cryptol-2.4.0/ 0000755 0000000 0000000 00000000000 12737220176 011406 5 ustar 00 0000000 0000000 cryptol-2.4.0/cryptol.cabal 0000644 0000000 0000000 00000023045 12737220176 014072 0 ustar 00 0000000 0000000 Name: cryptol
Version: 2.4.0
Synopsis: Cryptol: The Language of Cryptography
Description: Cryptol is a domain-specific language for specifying cryptographic algorithms. A Cryptol implementation of an algorithm resembles its mathematical specification more closely than an implementation in a general purpose language. For more, see .
License: BSD3
License-file: LICENSE
Author: Galois, Inc.
Maintainer: cryptol@galois.com
Homepage: http://www.cryptol.net/
Bug-reports: https://github.com/GaloisInc/cryptol/issues
Copyright: 2013-2016 Galois Inc.
Category: Language
Build-type: Simple
Cabal-version: >= 1.18
extra-source-files: bench/data/*.cry
data-files: *.cry Cryptol/*.cry
data-dir: lib
source-repository head
type: git
location: https://github.com/GaloisInc/cryptol.git
source-repository this
type: git
location: https://github.com/GaloisInc/cryptol.git
tag: 2.4.0
flag static
default: False
description: Create a statically-linked binary
flag relocatable
default: True
description: Don't use the Cabal-provided data directory for looking up Cryptol libraries. This is useful when the data directory can't be known ahead of time, like for a relocatable distribution.
flag server
default: False
description: Build with the ZeroMQ/JSON cryptol-server executable
library
Default-language:
Haskell98
Build-depends: base >= 4.8 && < 5,
base-compat >= 0.6,
bytestring >= 0.10,
array >= 0.4,
async >= 2.0,
containers >= 0.5,
deepseq >= 1.3,
directory >= 1.2.2.0,
filepath >= 1.3,
gitrev >= 1.0,
GraphSCC >= 1.0.4,
heredoc >= 0.2,
monad-control >= 1.0,
monadLib >= 3.7.2,
old-time >= 1.1,
presburger >= 1.3,
pretty >= 1.1,
process >= 1.2,
QuickCheck >= 2.7,
random >= 1.0.1,
sbv >= 5.12,
smtLib >= 1.0.7,
simple-smt >= 0.6.0,
syb >= 0.4,
text >= 1.1,
template-haskell,
tf-random >= 0.5,
transformers >= 0.3,
transformers-base >= 0.4,
utf8-string >= 0.3
Build-tools: alex, happy
hs-source-dirs: src
Exposed-modules: Cryptol.Prims.Syntax,
Cryptol.Prims.Eval,
Cryptol.Parser,
Cryptol.Parser.Lexer,
Cryptol.Parser.AST,
Cryptol.Parser.Position,
Cryptol.Parser.Names,
Cryptol.Parser.Name,
Cryptol.Parser.NoPat,
Cryptol.Parser.NoInclude,
Cryptol.Parser.Utils,
Cryptol.Parser.Unlit,
Cryptol.Utils.Ident,
Cryptol.Utils.PP,
Cryptol.Utils.Panic,
Cryptol.Utils.Debug,
Cryptol.Utils.Misc,
Cryptol.Version,
Cryptol.ModuleSystem,
Cryptol.ModuleSystem.Base,
Cryptol.ModuleSystem.Env,
Cryptol.ModuleSystem.Interface,
Cryptol.ModuleSystem.Monad,
Cryptol.ModuleSystem.Name,
Cryptol.ModuleSystem.NamingEnv,
Cryptol.ModuleSystem.Renamer,
Cryptol.TypeCheck,
Cryptol.TypeCheck.AST,
Cryptol.TypeCheck.Monad,
Cryptol.TypeCheck.Infer,
Cryptol.TypeCheck.InferTypes,
Cryptol.TypeCheck.Kind,
Cryptol.TypeCheck.Subst,
Cryptol.TypeCheck.Instantiate,
Cryptol.TypeCheck.Unify,
Cryptol.TypeCheck.Depends,
Cryptol.TypeCheck.PP,
Cryptol.TypeCheck.Solve,
Cryptol.TypeCheck.TypeMap,
Cryptol.TypeCheck.TypeOf,
Cryptol.TypeCheck.Sanity,
Cryptol.TypeCheck.Solver.InfNat,
Cryptol.TypeCheck.Solver.Class,
Cryptol.TypeCheck.Solver.Selector,
Cryptol.TypeCheck.Solver.Utils,
Cryptol.TypeCheck.Solver.Simplify,
Cryptol.TypeCheck.Solver.CrySAT,
Cryptol.TypeCheck.Solver.Numeric.AST,
Cryptol.TypeCheck.Solver.Numeric.ImportExport,
Cryptol.TypeCheck.Solver.Numeric.Defined,
Cryptol.TypeCheck.Solver.Numeric.Fin,
Cryptol.TypeCheck.Solver.Numeric.Interval,
Cryptol.TypeCheck.Solver.Numeric.Simplify,
Cryptol.TypeCheck.Solver.Numeric.Simplify1,
Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr,
Cryptol.TypeCheck.Solver.Numeric.NonLin,
Cryptol.TypeCheck.Solver.Numeric.SMT,
Cryptol.Transform.MonoValues,
Cryptol.Transform.Specialize,
Cryptol.Eval,
Cryptol.Eval.Arch,
Cryptol.Eval.Env,
Cryptol.Eval.Error,
Cryptol.Eval.Type,
Cryptol.Eval.Value,
Cryptol.Testing.Concrete,
Cryptol.Testing.Random,
Cryptol.Symbolic,
Cryptol.Symbolic.Prims,
Cryptol.Symbolic.Value,
Cryptol.REPL.Command,
Cryptol.REPL.Monad,
Cryptol.REPL.Trie
Other-modules: Cryptol.Parser.LexerUtils,
Cryptol.Parser.ParserUtils,
Cryptol.Prelude,
Paths_cryptol,
GitRev
GHC-options: -Wall -O2 -fsimpl-tick-factor=140
if impl(ghc >= 8.0.1)
ghc-options: -Wno-redundant-constraints
ghc-prof-options: -fprof-auto
if flag(relocatable)
cpp-options: -DRELOCATABLE
executable cryptol
Default-language:
Haskell98
Main-is: Main.hs
hs-source-dirs: cryptol
Other-modules: OptParser,
REPL.Haskeline,
REPL.Logo,
Paths_cryptol
build-depends: ansi-terminal
, base
, base-compat
, containers
, cryptol
, deepseq
, directory
, filepath
, haskeline
, monadLib
, monad-control
, process
, random
, sbv
, tf-random
, transformers
GHC-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N1
if impl(ghc >= 8.0.1)
ghc-options: -Wno-redundant-constraints
ghc-prof-options: -auto-all -rtsopts
if os(linux) && flag(static)
ld-options: -static -pthread
executable cryptol-server
main-is: Main.hs
hs-source-dirs: cryptol-server
other-modules: Cryptol.Aeson
default-language: Haskell2010
default-extensions: OverloadedStrings
GHC-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N1
if impl(ghc >= 8.0.1)
ghc-options: -Wno-redundant-constraints
ghc-prof-options: -auto-all -rtsopts
if os(linux) && flag(static)
ld-options: -static -pthread
if flag(server)
build-depends: aeson >= 0.10
, aeson-pretty >= 0.7
, base
, base-compat
, bytestring >= 0.10
, containers
, cryptol
, filepath
, monad-control
, optparse-applicative >= 0.12
, text
, transformers
, unix
, unordered-containers >= 0.2
, zeromq4-haskell >= 0.6
else
buildable: False
benchmark cryptol-bench
type: exitcode-stdio-1.0
main-is: Main.hs
hs-source-dirs: bench
default-language: Haskell2010
GHC-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N
if impl(ghc >= 8.0.1)
ghc-options: -Wno-redundant-constraints
ghc-prof-options: -auto-all -rtsopts
if os(linux) && flag(static)
ld-options: -static -pthread
build-depends: base
, criterion
, cryptol
, deepseq
, text
cryptol-2.4.0/LICENSE 0000644 0000000 0000000 00000002740 12737220176 012416 0 ustar 00 0000000 0000000 Copyright (c) 2013-2016 Galois Inc.
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
* Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in
the documentation and/or other materials provided with the
distribution.
* Neither the name of Galois, Inc. nor the names of its contributors
may be used to endorse or promote products derived from this
software without specific prior written permission.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A
PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER
OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
cryptol-2.4.0/Setup.hs 0000644 0000000 0000000 00000000361 12737220176 013042 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
import Distribution.Simple
main = defaultMain
cryptol-2.4.0/bench/ 0000755 0000000 0000000 00000000000 12737220176 012465 5 ustar 00 0000000 0000000 cryptol-2.4.0/bench/Main.hs 0000644 0000000 0000000 00000011275 12737220176 013713 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.IO as T
import qualified Cryptol.ModuleSystem.Base as M
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.ModuleSystem.Monad as M
import qualified Cryptol.ModuleSystem.NamingEnv as M
import qualified Cryptol.Parser as P
import qualified Cryptol.Parser.AST as P
import qualified Cryptol.Parser.NoInclude as P
import qualified Cryptol.Symbolic as S
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.Utils.Ident as I
import Criterion.Main
main :: IO ()
main = defaultMain [
bgroup "parser" [
parser "Prelude" "lib/Cryptol.cry"
, parser "BigSequence" "bench/data/BigSequence.cry"
, parser "BigSequenceHex" "bench/data/BigSequenceHex.cry"
, parser "AES" "bench/data/AES.cry"
, parser "SHA512" "bench/data/SHA512.cry"
]
, bgroup "typechecker" [
tc "Prelude" "lib/Cryptol.cry"
, tc "BigSequence" "bench/data/BigSequence.cry"
, tc "BigSequenceHex" "bench/data/BigSequenceHex.cry"
, tc "AES" "bench/data/AES.cry"
, tc "SHA512" "bench/data/SHA512.cry"
]
, bgroup "conc_eval" [
ceval "AES" "bench/data/AES.cry" "bench bench_data"
, ceval "SHA512" "bench/data/SHA512.cry" "testVector1 ()"
]
, bgroup "sym_eval" [
seval "AES" "bench/data/AES.cry" "aesEncrypt (zero, zero)"
, seval "ZUC" "bench/data/ZUC.cry"
"ZUC_isResistantToCollisionAttack"
, seval "SHA512" "bench/data/SHA512.cry" "testVector1 ()"
]
]
-- | Make a benchmark for parsing a Cryptol module
parser :: String -> FilePath -> Benchmark
parser name path =
env (T.readFile path) $ \(~bytes) ->
bench name $ nfIO $ do
let cfg = P.defaultConfig
{ P.cfgSource = path
, P.cfgPreProc = P.guessPreProc path
}
case P.parseModule cfg bytes of
Right pm -> return pm
Left err -> error (show err)
-- | Make a benchmark for typechecking a Cryptol module. Does parsing
-- in the setup phase in order to isolate typechecking
tc :: String -> FilePath -> Benchmark
tc name path =
let setup = do
bytes <- T.readFile path
let cfg = P.defaultConfig
{ P.cfgSource = path
, P.cfgPreProc = P.guessPreProc path
}
Right pm = P.parseModule cfg bytes
menv <- M.initialModuleEnv
(Right ((prims, scm, tcEnv), menv'), _) <- M.runModuleM menv $ do
-- code from `loadModule` and `checkModule` in
-- `Cryptol.ModuleSystem.Base`
let pm' = M.addPrelude pm
M.loadDeps pm'
Right nim <- M.io (P.removeIncludesModule path pm')
npm <- M.noPat nim
(tcEnv,declsEnv,scm) <- M.renameModule npm
prims <- if P.thing (P.mName pm) == I.preludeName
then return (M.toPrimMap declsEnv)
else M.getPrimMap
return (prims, scm, tcEnv)
return (prims, scm, tcEnv, menv')
in env setup $ \ ~(prims, scm, tcEnv, menv) ->
bench name $ nfIO $ M.runModuleM menv $ do
let act = M.TCAction { M.tcAction = T.tcModule
, M.tcLinter = M.moduleLinter (P.thing (P.mName scm))
, M.tcPrims = prims
}
M.typecheck act scm tcEnv
ceval :: String -> FilePath -> T.Text -> Benchmark
ceval name path expr =
let setup = do
menv <- M.initialModuleEnv
(Right (texpr, menv'), _) <- M.runModuleM menv $ do
m <- M.loadModuleByPath path
M.setFocusedModule (T.mName m)
let Right pexpr = P.parseExpr expr
(_, texpr, _) <- M.checkExpr pexpr
return texpr
return (texpr, menv')
in env setup $ \ ~(texpr, menv) ->
bench name $ nfIO $ M.runModuleM menv $ M.evalExpr texpr
seval :: String -> FilePath -> T.Text -> Benchmark
seval name path expr =
let setup = do
menv <- M.initialModuleEnv
(Right (texpr, menv'), _) <- M.runModuleM menv $ do
m <- M.loadModuleByPath path
M.setFocusedModule (T.mName m)
let Right pexpr = P.parseExpr expr
(_, texpr, _) <- M.checkExpr pexpr
return texpr
return (texpr, menv')
in env setup $ \ ~(texpr, menv) ->
bench name $ flip nf texpr $ \texpr' ->
let senv = S.evalDecls mempty (S.allDeclGroups menv)
in S.evalExpr senv texpr'
cryptol-2.4.0/bench/data/ 0000755 0000000 0000000 00000000000 12737220176 013376 5 ustar 00 0000000 0000000 cryptol-2.4.0/bench/data/AES.cry 0000644 0000000 0000000 00000021213 12737220176 014524 0 ustar 00 0000000 0000000 // Cryptol AES Implementation
// Copyright (c) 2010-2013, Galois Inc.
// www.cryptol.net
// You can freely use this source code for educational purposes.
// This is a fairly close implementation of the FIPS-197 standard:
// http://csrc.nist.gov/publications/fips/fips197/fips-197.pdf
// Nk: Number of blocks in the key
// Must be one of 4 (AES128), 6 (AES192), or 8 (AES256)
// Aside from this line, no other code below needs to change for
// implementing AES128, AES192, or AES256
module AES where
type AES128 = 4
type AES192 = 6
type AES256 = 8
type Nk = AES128
// For Cryptol 2.x | x > 0
// NkValid: `Nk -> Bit
// property NkValid k = (k == `AES128) || (k == `AES192) || (k == `AES256)
// Number of blocks and Number of rounds
type Nb = 4
type Nr = 6 + Nk
type AESKeySize = (Nk*32)
// Helper type definitions
type GF28 = [8]
type State = [4][Nb]GF28
type RoundKey = State
type KeySchedule = (RoundKey, [Nr-1]RoundKey, RoundKey)
// GF28 operations
gf28Add : {n} (fin n) => [n]GF28 -> GF28
gf28Add ps = sums ! 0
where sums = [zero] # [ p ^ s | p <- ps | s <- sums ]
irreducible = <| x^^8 + x^^4 + x^^3 + x + 1 |>
gf28Mult : (GF28, GF28) -> GF28
gf28Mult (x, y) = pmod(pmult x y) irreducible
gf28Pow : (GF28, [8]) -> GF28
gf28Pow (n, k) = pow k
where sq x = gf28Mult (x, x)
odd x = x ! 0
pow i = if i == 0 then 1
else if odd i
then gf28Mult(n, sq (pow (i >> 1)))
else sq (pow (i >> 1))
gf28Inverse : GF28 -> GF28
gf28Inverse x = gf28Pow (x, 254)
gf28DotProduct : {n} (fin n) => ([n]GF28, [n]GF28) -> GF28
gf28DotProduct (xs, ys) = gf28Add [ gf28Mult (x, y) | x <- xs
| y <- ys ]
gf28VectorMult : {n, m} (fin n) => ([n]GF28, [m][n]GF28) -> [m]GF28
gf28VectorMult (v, ms) = [ gf28DotProduct(v, m) | m <- ms ]
gf28MatrixMult : {n, m, k} (fin m) => ([n][m]GF28, [m][k]GF28) -> [n][k]GF28
gf28MatrixMult (xss, yss) = [ gf28VectorMult(xs, yss') | xs <- xss ]
where yss' = transpose yss
// The affine transform and its inverse
xformByte : GF28 -> GF28
xformByte b = gf28Add [b, (b >>> 4), (b >>> 5), (b >>> 6), (b >>> 7), c]
where c = 0x63
xformByte' : GF28 -> GF28
xformByte' b = gf28Add [(b >>> 2), (b >>> 5), (b >>> 7), d] where d = 0x05
// The SubBytes transform and its inverse
SubByte : GF28 -> GF28
SubByte b = xformByte (gf28Inverse b)
SubByte' : GF28 -> GF28
SubByte' b = sbox@b
SubBytes : State -> State
SubBytes state = [ [ SubByte' b | b <- row ] | row <- state ]
InvSubByte : GF28 -> GF28
InvSubByte b = gf28Inverse (xformByte' b)
InvSubBytes : State -> State
InvSubBytes state =[ [ InvSubByte b | b <- row ] | row <- state ]
// The ShiftRows transform and its inverse
ShiftRows : State -> State
ShiftRows state = [ row <<< shiftAmount | row <- state
| shiftAmount <- [0 .. 3]
]
InvShiftRows : State -> State
InvShiftRows state = [ row >>> shiftAmount | row <- state
| shiftAmount <- [0 .. 3]
]
// The MixColumns transform and its inverse
MixColumns : State -> State
MixColumns state = gf28MatrixMult (m, state)
where m = [[2, 3, 1, 1],
[1, 2, 3, 1],
[1, 1, 2, 3],
[3, 1, 1, 2]]
InvMixColumns : State -> State
InvMixColumns state = gf28MatrixMult (m, state)
where m = [[0x0e, 0x0b, 0x0d, 0x09],
[0x09, 0x0e, 0x0b, 0x0d],
[0x0d, 0x09, 0x0e, 0x0b],
[0x0b, 0x0d, 0x09, 0x0e]]
// The AddRoundKey transform
AddRoundKey : (RoundKey, State) -> State
AddRoundKey (rk, s) = rk ^ s
// Key expansion
Rcon : [8] -> [4]GF28
Rcon i = [(gf28Pow (<| x |>, i-1)), 0, 0, 0]
SubWord : [4]GF28 -> [4]GF28
SubWord bs = [ SubByte b | b <- bs ]
RotWord : [4]GF28 -> [4]GF28
RotWord [a0, a1, a2, a3] = [a1, a2, a3, a0]
NextWord : ([8],[4][8],[4][8]) -> [4][8]
NextWord(i, prev, old) = old ^ mask
where mask = if i % `Nk == 0
then SubWord(RotWord(prev)) ^ Rcon (i / `Nk)
else if (`Nk > 6) && (i % `Nk == 4)
then SubWord(prev)
else prev
ExpandKeyForever : [Nk][4][8] -> [inf]RoundKey
ExpandKeyForever seed = [ transpose g | g <- groupBy`{4} (keyWS seed) ]
keyWS : [Nk][4][8] -> [inf][4][8]
keyWS seed = xs
where xs = seed # [ NextWord(i, prev, old)
| i <- [ `Nk ... ]
| prev <- drop`{Nk-1} xs
| old <- xs
]
checkKey = take`{16} (drop`{8} (keyWS ["abcd", "defg", "1234", "5678"]))
checkKey2 = [transpose g | g <- groupBy`{4}checkKey]
ExpandKey : [AESKeySize] -> KeySchedule
ExpandKey key = (keys @ 0, keys @@ [1 .. (Nr - 1)], keys @ `Nr)
where seed : [Nk][4][8]
seed = split (split key)
keys = ExpandKeyForever seed
fromKS : KeySchedule -> [Nr+1][4][32]
fromKS (f, ms, l) = [ formKeyWords (transpose k) | k <- [f] # ms # [l] ]
where formKeyWords bbs = [ join bs | bs <- bbs ]
// AES rounds and inverses
AESRound : (RoundKey, State) -> State
AESRound (rk, s) = AddRoundKey (rk, MixColumns (ShiftRows (SubBytes s)))
AESFinalRound : (RoundKey, State) -> State
AESFinalRound (rk, s) = AddRoundKey (rk, ShiftRows (SubBytes s))
AESInvRound : (RoundKey, State) -> State
AESInvRound (rk, s) =
InvMixColumns (AddRoundKey (rk, InvSubBytes (InvShiftRows s)))
AESFinalInvRound : (RoundKey, State) -> State
AESFinalInvRound (rk, s) = AddRoundKey (rk, InvSubBytes (InvShiftRows s))
// Converting a 128 bit message to a State and back
msgToState : [128] -> State
msgToState msg = transpose (split (split msg))
stateToMsg : State -> [128]
stateToMsg st = join (join (transpose st))
// AES Encryption
aesEncrypt : ([128], [AESKeySize]) -> [128]
aesEncrypt (pt, key) = stateToMsg (AESFinalRound (kFinal, rounds ! 0))
where (kInit, ks, kFinal) = ExpandKey key
state0 = AddRoundKey(kInit, msgToState pt)
rounds = [state0] # [ AESRound (rk, s) | rk <- ks
| s <- rounds
]
// AES Decryption
aesDecrypt : ([128], [AESKeySize]) -> [128]
aesDecrypt (ct, key) = stateToMsg (AESFinalInvRound (kFinal, rounds ! 0))
where (kFinal, ks, kInit) = ExpandKey key
state0 = AddRoundKey(kInit, msgToState ct)
rounds = [state0] # [ AESInvRound (rk, s)
| rk <- reverse ks
| s <- rounds
]
sbox : [256]GF28
sbox = [
0x63, 0x7c, 0x77, 0x7b, 0xf2, 0x6b, 0x6f, 0xc5, 0x30, 0x01, 0x67,
0x2b, 0xfe, 0xd7, 0xab, 0x76, 0xca, 0x82, 0xc9, 0x7d, 0xfa, 0x59,
0x47, 0xf0, 0xad, 0xd4, 0xa2, 0xaf, 0x9c, 0xa4, 0x72, 0xc0, 0xb7,
0xfd, 0x93, 0x26, 0x36, 0x3f, 0xf7, 0xcc, 0x34, 0xa5, 0xe5, 0xf1,
0x71, 0xd8, 0x31, 0x15, 0x04, 0xc7, 0x23, 0xc3, 0x18, 0x96, 0x05,
0x9a, 0x07, 0x12, 0x80, 0xe2, 0xeb, 0x27, 0xb2, 0x75, 0x09, 0x83,
0x2c, 0x1a, 0x1b, 0x6e, 0x5a, 0xa0, 0x52, 0x3b, 0xd6, 0xb3, 0x29,
0xe3, 0x2f, 0x84, 0x53, 0xd1, 0x00, 0xed, 0x20, 0xfc, 0xb1, 0x5b,
0x6a, 0xcb, 0xbe, 0x39, 0x4a, 0x4c, 0x58, 0xcf, 0xd0, 0xef, 0xaa,
0xfb, 0x43, 0x4d, 0x33, 0x85, 0x45, 0xf9, 0x02, 0x7f, 0x50, 0x3c,
0x9f, 0xa8, 0x51, 0xa3, 0x40, 0x8f, 0x92, 0x9d, 0x38, 0xf5, 0xbc,
0xb6, 0xda, 0x21, 0x10, 0xff, 0xf3, 0xd2, 0xcd, 0x0c, 0x13, 0xec,
0x5f, 0x97, 0x44, 0x17, 0xc4, 0xa7, 0x7e, 0x3d, 0x64, 0x5d, 0x19,
0x73, 0x60, 0x81, 0x4f, 0xdc, 0x22, 0x2a, 0x90, 0x88, 0x46, 0xee,
0xb8, 0x14, 0xde, 0x5e, 0x0b, 0xdb, 0xe0, 0x32, 0x3a, 0x0a, 0x49,
0x06, 0x24, 0x5c, 0xc2, 0xd3, 0xac, 0x62, 0x91, 0x95, 0xe4, 0x79,
0xe7, 0xc8, 0x37, 0x6d, 0x8d, 0xd5, 0x4e, 0xa9, 0x6c, 0x56, 0xf4,
0xea, 0x65, 0x7a, 0xae, 0x08, 0xba, 0x78, 0x25, 0x2e, 0x1c, 0xa6,
0xb4, 0xc6, 0xe8, 0xdd, 0x74, 0x1f, 0x4b, 0xbd, 0x8b, 0x8a, 0x70,
0x3e, 0xb5, 0x66, 0x48, 0x03, 0xf6, 0x0e, 0x61, 0x35, 0x57, 0xb9,
0x86, 0xc1, 0x1d, 0x9e, 0xe1, 0xf8, 0x98, 0x11, 0x69, 0xd9, 0x8e,
0x94, 0x9b, 0x1e, 0x87, 0xe9, 0xce, 0x55, 0x28, 0xdf, 0x8c, 0xa1,
0x89, 0x0d, 0xbf, 0xe6, 0x42, 0x68, 0x41, 0x99, 0x2d, 0x0f, 0xb0,
0x54, 0xbb, 0x16]
// Test runs:
// cryptol> aesEncrypt (0x3243f6a8885a308d313198a2e0370734, \
// 0x2b7e151628aed2a6abf7158809cf4f3c)
// 0x3925841d02dc09fbdc118597196a0b32
// cryptol> aesEncrypt (0x00112233445566778899aabbccddeeff, \
// 0x000102030405060708090a0b0c0d0e0f)
// 0x69c4e0d86a7b0430d8cdb78070b4c55a
property AESCorrect msg key = aesDecrypt (aesEncrypt (msg, key), key) == msg
// Benchmark:
type nblocks = 128
bench_data : [128 * nblocks]
bench_data = random 0
bench : [128 * nblocks] -> [128 * nblocks]
bench data = join [ aesEncrypt (block, key) | block <- split data ]
where key = 0x3243f6a8885a308d313198a2e0370734 cryptol-2.4.0/bench/data/BigSequence.cry 0000644 0000000 0000000 00000045661 12737220176 016323 0 ustar 00 0000000 0000000 xs = [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63,64,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,90,91,92,93,94,95,96,97,98,99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,114,115,116,117,118,119,120,121,122,123,124,125,126,127,128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143,144,145,146,147,148,149,150,151,152,153,154,155,156,157,158,159,160,161,162,163,164,165,166,167,168,169,170,171,172,173,174,175,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207,208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223,224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244,245,246,247,248,249,250,251,252,253,254,255,256,257,258,259,260,261,262,263,264,265,266,267,268,269,270,271,272,273,274,275,276,277,278,279,280,281,282,283,284,285,286,287,288,289,290,291,292,293,294,295,296,297,298,299,300,301,302,303,304,305,306,307,308,309,310,311,312,313,314,315,316,317,318,319,320,321,322,323,324,325,326,327,328,329,330,331,332,333,334,335,336,337,338,339,340,341,342,343,344,345,346,347,348,349,350,351,352,353,354,355,356,357,358,359,360,361,362,363,364,365,366,367,368,369,370,371,372,373,374,375,376,377,378,379,380,381,382,383,384,385,386,387,388,389,390,391,392,393,394,395,396,397,398,399,400,401,402,403,404,405,406,407,408,409,410,411,412,413,414,415,416,417,418,419,420,421,422,423,424,425,426,427,428,429,430,431,432,433,434,435,436,437,438,439,440,441,442,443,444,445,446,447,448,449,450,451,452,453,454,455,456,457,458,459,460,461,462,463,464,465,466,467,468,469,470,471,472,473,474,475,476,477,478,479,480,481,482,483,484,485,486,487,488,489,490,491,492,493,494,495,496,497,498,499,500,501,502,503,504,505,506,507,508,509,510,511,512,513,514,515,516,517,518,519,520,521,522,523,524,525,526,527,528,529,530,531,532,533,534,535,536,537,538,539,540,541,542,543,544,545,546,547,548,549,550,551,552,553,554,555,556,557,558,559,560,561,562,563,564,565,566,567,568,569,570,571,572,573,574,575,576,577,578,579,580,581,582,583,584,585,586,587,588,589,590,591,592,593,594,595,596,597,598,599,600,601,602,603,604,605,606,607,608,609,610,611,612,613,614,615,616,617,618,619,620,621,622,623,624,625,626,627,628,629,630,631,632,633,634,635,636,637,638,639,640,641,642,643,644,645,646,647,648,649,650,651,652,653,654,655,656,657,658,659,660,661,662,663,664,665,666,667,668,669,670,671,672,673,674,675,676,677,678,679,680,681,682,683,684,685,686,687,688,689,690,691,692,693,694,695,696,697,698,699,700,701,702,703,704,705,706,707,708,709,710,711,712,713,714,715,716,717,718,719,720,721,722,723,724,725,726,727,728,729,730,731,732,733,734,735,736,737,738,739,740,741,742,743,744,745,746,747,748,749,750,751,752,753,754,755,756,757,758,759,760,761,762,763,764,765,766,767,768,769,770,771,772,773,774,775,776,777,778,779,780,781,782,783,784,785,786,787,788,789,790,791,792,793,794,795,796,797,798,799,800,801,802,803,804,805,806,807,808,809,810,811,812,813,814,815,816,817,818,819,820,821,822,823,824,825,826,827,828,829,830,831,832,833,834,835,836,837,838,839,840,841,842,843,844,845,846,847,848,849,850,851,852,853,854,855,856,857,858,859,860,861,862,863,864,865,866,867,868,869,870,871,872,873,874,875,876,877,878,879,880,881,882,883,884,885,886,887,888,889,890,891,892,893,894,895,896,897,898,899,900,901,902,903,904,905,906,907,908,909,910,911,912,913,914,915,916,917,918,919,920,921,922,923,924,925,926,927,928,929,930,931,932,933,934,935,936,937,938,939,940,941,942,943,944,945,946,947,948,949,950,951,952,953,954,955,956,957,958,959,960,961,962,963,964,965,966,967,968,969,970,971,972,973,974,975,976,977,978,979,980,981,982,983,984,985,986,987,988,989,990,991,992,993,994,995,996,997,998,999,1000,1001,1002,1003,1004,1005,1006,1007,1008,1009,1010,1011,1012,1013,1014,1015,1016,1017,1018,1019,1020,1021,1022,1023,1024,1025,1026,1027,1028,1029,1030,1031,1032,1033,1034,1035,1036,1037,1038,1039,1040,1041,1042,1043,1044,1045,1046,1047,1048,1049,1050,1051,1052,1053,1054,1055,1056,1057,1058,1059,1060,1061,1062,1063,1064,1065,1066,1067,1068,1069,1070,1071,1072,1073,1074,1075,1076,1077,1078,1079,1080,1081,1082,1083,1084,1085,1086,1087,1088,1089,1090,1091,1092,1093,1094,1095,1096,1097,1098,1099,1100,1101,1102,1103,1104,1105,1106,1107,1108,1109,1110,1111,1112,1113,1114,1115,1116,1117,1118,1119,1120,1121,1122,1123,1124,1125,1126,1127,1128,1129,1130,1131,1132,1133,1134,1135,1136,1137,1138,1139,1140,1141,1142,1143,1144,1145,1146,1147,1148,1149,1150,1151,1152,1153,1154,1155,1156,1157,1158,1159,1160,1161,1162,1163,1164,1165,1166,1167,1168,1169,1170,1171,1172,1173,1174,1175,1176,1177,1178,1179,1180,1181,1182,1183,1184,1185,1186,1187,1188,1189,1190,1191,1192,1193,1194,1195,1196,1197,1198,1199,1200,1201,1202,1203,1204,1205,1206,1207,1208,1209,1210,1211,1212,1213,1214,1215,1216,1217,1218,1219,1220,1221,1222,1223,1224,1225,1226,1227,1228,1229,1230,1231,1232,1233,1234,1235,1236,1237,1238,1239,1240,1241,1242,1243,1244,1245,1246,1247,1248,1249,1250,1251,1252,1253,1254,1255,1256,1257,1258,1259,1260,1261,1262,1263,1264,1265,1266,1267,1268,1269,1270,1271,1272,1273,1274,1275,1276,1277,1278,1279,1280,1281,1282,1283,1284,1285,1286,1287,1288,1289,1290,1291,1292,1293,1294,1295,1296,1297,1298,1299,1300,1301,1302,1303,1304,1305,1306,1307,1308,1309,1310,1311,1312,1313,1314,1315,1316,1317,1318,1319,1320,1321,1322,1323,1324,1325,1326,1327,1328,1329,1330,1331,1332,1333,1334,1335,1336,1337,1338,1339,1340,1341,1342,1343,1344,1345,1346,1347,1348,1349,1350,1351,1352,1353,1354,1355,1356,1357,1358,1359,1360,1361,1362,1363,1364,1365,1366,1367,1368,1369,1370,1371,1372,1373,1374,1375,1376,1377,1378,1379,1380,1381,1382,1383,1384,1385,1386,1387,1388,1389,1390,1391,1392,1393,1394,1395,1396,1397,1398,1399,1400,1401,1402,1403,1404,1405,1406,1407,1408,1409,1410,1411,1412,1413,1414,1415,1416,1417,1418,1419,1420,1421,1422,1423,1424,1425,1426,1427,1428,1429,1430,1431,1432,1433,1434,1435,1436,1437,1438,1439,1440,1441,1442,1443,1444,1445,1446,1447,1448,1449,1450,1451,1452,1453,1454,1455,1456,1457,1458,1459,1460,1461,1462,1463,1464,1465,1466,1467,1468,1469,1470,1471,1472,1473,1474,1475,1476,1477,1478,1479,1480,1481,1482,1483,1484,1485,1486,1487,1488,1489,1490,1491,1492,1493,1494,1495,1496,1497,1498,1499,1500,1501,1502,1503,1504,1505,1506,1507,1508,1509,1510,1511,1512,1513,1514,1515,1516,1517,1518,1519,1520,1521,1522,1523,1524,1525,1526,1527,1528,1529,1530,1531,1532,1533,1534,1535,1536,1537,1538,1539,1540,1541,1542,1543,1544,1545,1546,1547,1548,1549,1550,1551,1552,1553,1554,1555,1556,1557,1558,1559,1560,1561,1562,1563,1564,1565,1566,1567,1568,1569,1570,1571,1572,1573,1574,1575,1576,1577,1578,1579,1580,1581,1582,1583,1584,1585,1586,1587,1588,1589,1590,1591,1592,1593,1594,1595,1596,1597,1598,1599,1600,1601,1602,1603,1604,1605,1606,1607,1608,1609,1610,1611,1612,1613,1614,1615,1616,1617,1618,1619,1620,1621,1622,1623,1624,1625,1626,1627,1628,1629,1630,1631,1632,1633,1634,1635,1636,1637,1638,1639,1640,1641,1642,1643,1644,1645,1646,1647,1648,1649,1650,1651,1652,1653,1654,1655,1656,1657,1658,1659,1660,1661,1662,1663,1664,1665,1666,1667,1668,1669,1670,1671,1672,1673,1674,1675,1676,1677,1678,1679,1680,1681,1682,1683,1684,1685,1686,1687,1688,1689,1690,1691,1692,1693,1694,1695,1696,1697,1698,1699,1700,1701,1702,1703,1704,1705,1706,1707,1708,1709,1710,1711,1712,1713,1714,1715,1716,1717,1718,1719,1720,1721,1722,1723,1724,1725,1726,1727,1728,1729,1730,1731,1732,1733,1734,1735,1736,1737,1738,1739,1740,1741,1742,1743,1744,1745,1746,1747,1748,1749,1750,1751,1752,1753,1754,1755,1756,1757,1758,1759,1760,1761,1762,1763,1764,1765,1766,1767,1768,1769,1770,1771,1772,1773,1774,1775,1776,1777,1778,1779,1780,1781,1782,1783,1784,1785,1786,1787,1788,1789,1790,1791,1792,1793,1794,1795,1796,1797,1798,1799,1800,1801,1802,1803,1804,1805,1806,1807,1808,1809,1810,1811,1812,1813,1814,1815,1816,1817,1818,1819,1820,1821,1822,1823,1824,1825,1826,1827,1828,1829,1830,1831,1832,1833,1834,1835,1836,1837,1838,1839,1840,1841,1842,1843,1844,1845,1846,1847,1848,1849,1850,1851,1852,1853,1854,1855,1856,1857,1858,1859,1860,1861,1862,1863,1864,1865,1866,1867,1868,1869,1870,1871,1872,1873,1874,1875,1876,1877,1878,1879,1880,1881,1882,1883,1884,1885,1886,1887,1888,1889,1890,1891,1892,1893,1894,1895,1896,1897,1898,1899,1900,1901,1902,1903,1904,1905,1906,1907,1908,1909,1910,1911,1912,1913,1914,1915,1916,1917,1918,1919,1920,1921,1922,1923,1924,1925,1926,1927,1928,1929,1930,1931,1932,1933,1934,1935,1936,1937,1938,1939,1940,1941,1942,1943,1944,1945,1946,1947,1948,1949,1950,1951,1952,1953,1954,1955,1956,1957,1958,1959,1960,1961,1962,1963,1964,1965,1966,1967,1968,1969,1970,1971,1972,1973,1974,1975,1976,1977,1978,1979,1980,1981,1982,1983,1984,1985,1986,1987,1988,1989,1990,1991,1992,1993,1994,1995,1996,1997,1998,1999,2000,2001,2002,2003,2004,2005,2006,2007,2008,2009,2010,2011,2012,2013,2014,2015,2016,2017,2018,2019,2020,2021,2022,2023,2024,2025,2026,2027,2028,2029,2030,2031,2032,2033,2034,2035,2036,2037,2038,2039,2040,2041,2042,2043,2044,2045,2046,2047,2048,2049,2050,2051,2052,2053,2054,2055,2056,2057,2058,2059,2060,2061,2062,2063,2064,2065,2066,2067,2068,2069,2070,2071,2072,2073,2074,2075,2076,2077,2078,2079,2080,2081,2082,2083,2084,2085,2086,2087,2088,2089,2090,2091,2092,2093,2094,2095,2096,2097,2098,2099,2100,2101,2102,2103,2104,2105,2106,2107,2108,2109,2110,2111,2112,2113,2114,2115,2116,2117,2118,2119,2120,2121,2122,2123,2124,2125,2126,2127,2128,2129,2130,2131,2132,2133,2134,2135,2136,2137,2138,2139,2140,2141,2142,2143,2144,2145,2146,2147,2148,2149,2150,2151,2152,2153,2154,2155,2156,2157,2158,2159,2160,2161,2162,2163,2164,2165,2166,2167,2168,2169,2170,2171,2172,2173,2174,2175,2176,2177,2178,2179,2180,2181,2182,2183,2184,2185,2186,2187,2188,2189,2190,2191,2192,2193,2194,2195,2196,2197,2198,2199,2200,2201,2202,2203,2204,2205,2206,2207,2208,2209,2210,2211,2212,2213,2214,2215,2216,2217,2218,2219,2220,2221,2222,2223,2224,2225,2226,2227,2228,2229,2230,2231,2232,2233,2234,2235,2236,2237,2238,2239,2240,2241,2242,2243,2244,2245,2246,2247,2248,2249,2250,2251,2252,2253,2254,2255,2256,2257,2258,2259,2260,2261,2262,2263,2264,2265,2266,2267,2268,2269,2270,2271,2272,2273,2274,2275,2276,2277,2278,2279,2280,2281,2282,2283,2284,2285,2286,2287,2288,2289,2290,2291,2292,2293,2294,2295,2296,2297,2298,2299,2300,2301,2302,2303,2304,2305,2306,2307,2308,2309,2310,2311,2312,2313,2314,2315,2316,2317,2318,2319,2320,2321,2322,2323,2324,2325,2326,2327,2328,2329,2330,2331,2332,2333,2334,2335,2336,2337,2338,2339,2340,2341,2342,2343,2344,2345,2346,2347,2348,2349,2350,2351,2352,2353,2354,2355,2356,2357,2358,2359,2360,2361,2362,2363,2364,2365,2366,2367,2368,2369,2370,2371,2372,2373,2374,2375,2376,2377,2378,2379,2380,2381,2382,2383,2384,2385,2386,2387,2388,2389,2390,2391,2392,2393,2394,2395,2396,2397,2398,2399,2400,2401,2402,2403,2404,2405,2406,2407,2408,2409,2410,2411,2412,2413,2414,2415,2416,2417,2418,2419,2420,2421,2422,2423,2424,2425,2426,2427,2428,2429,2430,2431,2432,2433,2434,2435,2436,2437,2438,2439,2440,2441,2442,2443,2444,2445,2446,2447,2448,2449,2450,2451,2452,2453,2454,2455,2456,2457,2458,2459,2460,2461,2462,2463,2464,2465,2466,2467,2468,2469,2470,2471,2472,2473,2474,2475,2476,2477,2478,2479,2480,2481,2482,2483,2484,2485,2486,2487,2488,2489,2490,2491,2492,2493,2494,2495,2496,2497,2498,2499,2500,2501,2502,2503,2504,2505,2506,2507,2508,2509,2510,2511,2512,2513,2514,2515,2516,2517,2518,2519,2520,2521,2522,2523,2524,2525,2526,2527,2528,2529,2530,2531,2532,2533,2534,2535,2536,2537,2538,2539,2540,2541,2542,2543,2544,2545,2546,2547,2548,2549,2550,2551,2552,2553,2554,2555,2556,2557,2558,2559,2560,2561,2562,2563,2564,2565,2566,2567,2568,2569,2570,2571,2572,2573,2574,2575,2576,2577,2578,2579,2580,2581,2582,2583,2584,2585,2586,2587,2588,2589,2590,2591,2592,2593,2594,2595,2596,2597,2598,2599,2600,2601,2602,2603,2604,2605,2606,2607,2608,2609,2610,2611,2612,2613,2614,2615,2616,2617,2618,2619,2620,2621,2622,2623,2624,2625,2626,2627,2628,2629,2630,2631,2632,2633,2634,2635,2636,2637,2638,2639,2640,2641,2642,2643,2644,2645,2646,2647,2648,2649,2650,2651,2652,2653,2654,2655,2656,2657,2658,2659,2660,2661,2662,2663,2664,2665,2666,2667,2668,2669,2670,2671,2672,2673,2674,2675,2676,2677,2678,2679,2680,2681,2682,2683,2684,2685,2686,2687,2688,2689,2690,2691,2692,2693,2694,2695,2696,2697,2698,2699,2700,2701,2702,2703,2704,2705,2706,2707,2708,2709,2710,2711,2712,2713,2714,2715,2716,2717,2718,2719,2720,2721,2722,2723,2724,2725,2726,2727,2728,2729,2730,2731,2732,2733,2734,2735,2736,2737,2738,2739,2740,2741,2742,2743,2744,2745,2746,2747,2748,2749,2750,2751,2752,2753,2754,2755,2756,2757,2758,2759,2760,2761,2762,2763,2764,2765,2766,2767,2768,2769,2770,2771,2772,2773,2774,2775,2776,2777,2778,2779,2780,2781,2782,2783,2784,2785,2786,2787,2788,2789,2790,2791,2792,2793,2794,2795,2796,2797,2798,2799,2800,2801,2802,2803,2804,2805,2806,2807,2808,2809,2810,2811,2812,2813,2814,2815,2816,2817,2818,2819,2820,2821,2822,2823,2824,2825,2826,2827,2828,2829,2830,2831,2832,2833,2834,2835,2836,2837,2838,2839,2840,2841,2842,2843,2844,2845,2846,2847,2848,2849,2850,2851,2852,2853,2854,2855,2856,2857,2858,2859,2860,2861,2862,2863,2864,2865,2866,2867,2868,2869,2870,2871,2872,2873,2874,2875,2876,2877,2878,2879,2880,2881,2882,2883,2884,2885,2886,2887,2888,2889,2890,2891,2892,2893,2894,2895,2896,2897,2898,2899,2900,2901,2902,2903,2904,2905,2906,2907,2908,2909,2910,2911,2912,2913,2914,2915,2916,2917,2918,2919,2920,2921,2922,2923,2924,2925,2926,2927,2928,2929,2930,2931,2932,2933,2934,2935,2936,2937,2938,2939,2940,2941,2942,2943,2944,2945,2946,2947,2948,2949,2950,2951,2952,2953,2954,2955,2956,2957,2958,2959,2960,2961,2962,2963,2964,2965,2966,2967,2968,2969,2970,2971,2972,2973,2974,2975,2976,2977,2978,2979,2980,2981,2982,2983,2984,2985,2986,2987,2988,2989,2990,2991,2992,2993,2994,2995,2996,2997,2998,2999,3000,3001,3002,3003,3004,3005,3006,3007,3008,3009,3010,3011,3012,3013,3014,3015,3016,3017,3018,3019,3020,3021,3022,3023,3024,3025,3026,3027,3028,3029,3030,3031,3032,3033,3034,3035,3036,3037,3038,3039,3040,3041,3042,3043,3044,3045,3046,3047,3048,3049,3050,3051,3052,3053,3054,3055,3056,3057,3058,3059,3060,3061,3062,3063,3064,3065,3066,3067,3068,3069,3070,3071,3072,3073,3074,3075,3076,3077,3078,3079,3080,3081,3082,3083,3084,3085,3086,3087,3088,3089,3090,3091,3092,3093,3094,3095,3096,3097,3098,3099,3100,3101,3102,3103,3104,3105,3106,3107,3108,3109,3110,3111,3112,3113,3114,3115,3116,3117,3118,3119,3120,3121,3122,3123,3124,3125,3126,3127,3128,3129,3130,3131,3132,3133,3134,3135,3136,3137,3138,3139,3140,3141,3142,3143,3144,3145,3146,3147,3148,3149,3150,3151,3152,3153,3154,3155,3156,3157,3158,3159,3160,3161,3162,3163,3164,3165,3166,3167,3168,3169,3170,3171,3172,3173,3174,3175,3176,3177,3178,3179,3180,3181,3182,3183,3184,3185,3186,3187,3188,3189,3190,3191,3192,3193,3194,3195,3196,3197,3198,3199,3200,3201,3202,3203,3204,3205,3206,3207,3208,3209,3210,3211,3212,3213,3214,3215,3216,3217,3218,3219,3220,3221,3222,3223,3224,3225,3226,3227,3228,3229,3230,3231,3232,3233,3234,3235,3236,3237,3238,3239,3240,3241,3242,3243,3244,3245,3246,3247,3248,3249,3250,3251,3252,3253,3254,3255,3256,3257,3258,3259,3260,3261,3262,3263,3264,3265,3266,3267,3268,3269,3270,3271,3272,3273,3274,3275,3276,3277,3278,3279,3280,3281,3282,3283,3284,3285,3286,3287,3288,3289,3290,3291,3292,3293,3294,3295,3296,3297,3298,3299,3300,3301,3302,3303,3304,3305,3306,3307,3308,3309,3310,3311,3312,3313,3314,3315,3316,3317,3318,3319,3320,3321,3322,3323,3324,3325,3326,3327,3328,3329,3330,3331,3332,3333,3334,3335,3336,3337,3338,3339,3340,3341,3342,3343,3344,3345,3346,3347,3348,3349,3350,3351,3352,3353,3354,3355,3356,3357,3358,3359,3360,3361,3362,3363,3364,3365,3366,3367,3368,3369,3370,3371,3372,3373,3374,3375,3376,3377,3378,3379,3380,3381,3382,3383,3384,3385,3386,3387,3388,3389,3390,3391,3392,3393,3394,3395,3396,3397,3398,3399,3400,3401,3402,3403,3404,3405,3406,3407,3408,3409,3410,3411,3412,3413,3414,3415,3416,3417,3418,3419,3420,3421,3422,3423,3424,3425,3426,3427,3428,3429,3430,3431,3432,3433,3434,3435,3436,3437,3438,3439,3440,3441,3442,3443,3444,3445,3446,3447,3448,3449,3450,3451,3452,3453,3454,3455,3456,3457,3458,3459,3460,3461,3462,3463,3464,3465,3466,3467,3468,3469,3470,3471,3472,3473,3474,3475,3476,3477,3478,3479,3480,3481,3482,3483,3484,3485,3486,3487,3488,3489,3490,3491,3492,3493,3494,3495,3496,3497,3498,3499,3500,3501,3502,3503,3504,3505,3506,3507,3508,3509,3510,3511,3512,3513,3514,3515,3516,3517,3518,3519,3520,3521,3522,3523,3524,3525,3526,3527,3528,3529,3530,3531,3532,3533,3534,3535,3536,3537,3538,3539,3540,3541,3542,3543,3544,3545,3546,3547,3548,3549,3550,3551,3552,3553,3554,3555,3556,3557,3558,3559,3560,3561,3562,3563,3564,3565,3566,3567,3568,3569,3570,3571,3572,3573,3574,3575,3576,3577,3578,3579,3580,3581,3582,3583,3584,3585,3586,3587,3588,3589,3590,3591,3592,3593,3594,3595,3596,3597,3598,3599,3600,3601,3602,3603,3604,3605,3606,3607,3608,3609,3610,3611,3612,3613,3614,3615,3616,3617,3618,3619,3620,3621,3622,3623,3624,3625,3626,3627,3628,3629,3630,3631,3632,3633,3634,3635,3636,3637,3638,3639,3640,3641,3642,3643,3644,3645,3646,3647,3648,3649,3650,3651,3652,3653,3654,3655,3656,3657,3658,3659,3660,3661,3662,3663,3664,3665,3666,3667,3668,3669,3670,3671,3672,3673,3674,3675,3676,3677,3678,3679,3680,3681,3682,3683,3684,3685,3686,3687,3688,3689,3690,3691,3692,3693,3694,3695,3696,3697,3698,3699,3700,3701,3702,3703,3704,3705,3706,3707,3708,3709,3710,3711,3712,3713,3714,3715,3716,3717,3718,3719,3720,3721,3722,3723,3724,3725,3726,3727,3728,3729,3730,3731,3732,3733,3734,3735,3736,3737,3738,3739,3740,3741,3742,3743,3744,3745,3746,3747,3748,3749,3750,3751,3752,3753,3754,3755,3756,3757,3758,3759,3760,3761,3762,3763,3764,3765,3766,3767,3768,3769,3770,3771,3772,3773,3774,3775,3776,3777,3778,3779,3780,3781,3782,3783,3784,3785,3786,3787,3788,3789,3790,3791,3792,3793,3794,3795,3796,3797,3798,3799,3800,3801,3802,3803,3804,3805,3806,3807,3808,3809,3810,3811,3812,3813,3814,3815,3816,3817,3818,3819,3820,3821,3822,3823,3824,3825,3826,3827,3828,3829,3830,3831,3832,3833,3834,3835,3836,3837,3838,3839,3840,3841,3842,3843,3844,3845,3846,3847,3848,3849,3850,3851,3852,3853,3854,3855,3856,3857,3858,3859,3860,3861,3862,3863,3864,3865,3866,3867,3868,3869,3870,3871,3872,3873,3874,3875,3876,3877,3878,3879,3880,3881,3882,3883,3884,3885,3886,3887,3888,3889,3890,3891,3892,3893,3894,3895,3896,3897,3898,3899,3900,3901,3902,3903,3904,3905,3906,3907,3908,3909,3910,3911,3912,3913,3914,3915,3916,3917,3918,3919,3920,3921,3922,3923,3924,3925,3926,3927,3928,3929,3930,3931,3932,3933,3934,3935,3936,3937,3938,3939,3940,3941,3942,3943,3944,3945,3946,3947,3948,3949,3950,3951,3952,3953,3954,3955,3956,3957,3958,3959,3960,3961,3962,3963,3964,3965,3966,3967,3968,3969,3970,3971,3972,3973,3974,3975,3976,3977,3978,3979,3980,3981,3982,3983,3984,3985,3986,3987,3988,3989,3990,3991,3992,3993,3994,3995,3996,3997,3998,3999,4000,4001,4002,4003,4004,4005,4006,4007,4008,4009,4010,4011,4012,4013,4014,4015,4016,4017,4018,4019,4020,4021,4022,4023,4024,4025,4026,4027,4028,4029,4030,4031,4032,4033,4034,4035,4036,4037,4038,4039,4040,4041,4042,4043,4044,4045,4046,4047,4048,4049,4050,4051,4052,4053,4054,4055,4056,4057,4058,4059,4060,4061,4062,4063,4064,4065,4066,4067,4068,4069,4070,4071,4072,4073,4074,4075,4076,4077,4078,4079,4080,4081,4082,4083,4084,4085,4086,4087,4088,4089,4090,4091,4092,4093,4094,4095]
cryptol-2.4.0/bench/data/BigSequenceHex.cry 0000644 0000000 0000000 00000070005 12737220176 016756 0 ustar 00 0000000 0000000 xs = [0x000, 0x001, 0x002, 0x003, 0x004, 0x005, 0x006, 0x007, 0x008, 0x009, 0x00a, 0x00b, 0x00c, 0x00d, 0x00e, 0x00f, 0x010, 0x011, 0x012, 0x013, 0x014, 0x015, 0x016, 0x017, 0x018, 0x019, 0x01a, 0x01b, 0x01c, 0x01d, 0x01e, 0x01f, 0x020, 0x021, 0x022, 0x023, 0x024, 0x025, 0x026, 0x027, 0x028, 0x029, 0x02a, 0x02b, 0x02c, 0x02d, 0x02e, 0x02f, 0x030, 0x031, 0x032, 0x033, 0x034, 0x035, 0x036, 0x037, 0x038, 0x039, 0x03a, 0x03b, 0x03c, 0x03d, 0x03e, 0x03f, 0x040, 0x041, 0x042, 0x043, 0x044, 0x045, 0x046, 0x047, 0x048, 0x049, 0x04a, 0x04b, 0x04c, 0x04d, 0x04e, 0x04f, 0x050, 0x051, 0x052, 0x053, 0x054, 0x055, 0x056, 0x057, 0x058, 0x059, 0x05a, 0x05b, 0x05c, 0x05d, 0x05e, 0x05f, 0x060, 0x061, 0x062, 0x063, 0x064, 0x065, 0x066, 0x067, 0x068, 0x069, 0x06a, 0x06b, 0x06c, 0x06d, 0x06e, 0x06f, 0x070, 0x071, 0x072, 0x073, 0x074, 0x075, 0x076, 0x077, 0x078, 0x079, 0x07a, 0x07b, 0x07c, 0x07d, 0x07e, 0x07f, 0x080, 0x081, 0x082, 0x083, 0x084, 0x085, 0x086, 0x087, 0x088, 0x089, 0x08a, 0x08b, 0x08c, 0x08d, 0x08e, 0x08f, 0x090, 0x091, 0x092, 0x093, 0x094, 0x095, 0x096, 0x097, 0x098, 0x099, 0x09a, 0x09b, 0x09c, 0x09d, 0x09e, 0x09f, 0x0a0, 0x0a1, 0x0a2, 0x0a3, 0x0a4, 0x0a5, 0x0a6, 0x0a7, 0x0a8, 0x0a9, 0x0aa, 0x0ab, 0x0ac, 0x0ad, 0x0ae, 0x0af, 0x0b0, 0x0b1, 0x0b2, 0x0b3, 0x0b4, 0x0b5, 0x0b6, 0x0b7, 0x0b8, 0x0b9, 0x0ba, 0x0bb, 0x0bc, 0x0bd, 0x0be, 0x0bf, 0x0c0, 0x0c1, 0x0c2, 0x0c3, 0x0c4, 0x0c5, 0x0c6, 0x0c7, 0x0c8, 0x0c9, 0x0ca, 0x0cb, 0x0cc, 0x0cd, 0x0ce, 0x0cf, 0x0d0, 0x0d1, 0x0d2, 0x0d3, 0x0d4, 0x0d5, 0x0d6, 0x0d7, 0x0d8, 0x0d9, 0x0da, 0x0db, 0x0dc, 0x0dd, 0x0de, 0x0df, 0x0e0, 0x0e1, 0x0e2, 0x0e3, 0x0e4, 0x0e5, 0x0e6, 0x0e7, 0x0e8, 0x0e9, 0x0ea, 0x0eb, 0x0ec, 0x0ed, 0x0ee, 0x0ef, 0x0f0, 0x0f1, 0x0f2, 0x0f3, 0x0f4, 0x0f5, 0x0f6, 0x0f7, 0x0f8, 0x0f9, 0x0fa, 0x0fb, 0x0fc, 0x0fd, 0x0fe, 0x0ff, 0x100, 0x101, 0x102, 0x103, 0x104, 0x105, 0x106, 0x107, 0x108, 0x109, 0x10a, 0x10b, 0x10c, 0x10d, 0x10e, 0x10f, 0x110, 0x111, 0x112, 0x113, 0x114, 0x115, 0x116, 0x117, 0x118, 0x119, 0x11a, 0x11b, 0x11c, 0x11d, 0x11e, 0x11f, 0x120, 0x121, 0x122, 0x123, 0x124, 0x125, 0x126, 0x127, 0x128, 0x129, 0x12a, 0x12b, 0x12c, 0x12d, 0x12e, 0x12f, 0x130, 0x131, 0x132, 0x133, 0x134, 0x135, 0x136, 0x137, 0x138, 0x139, 0x13a, 0x13b, 0x13c, 0x13d, 0x13e, 0x13f, 0x140, 0x141, 0x142, 0x143, 0x144, 0x145, 0x146, 0x147, 0x148, 0x149, 0x14a, 0x14b, 0x14c, 0x14d, 0x14e, 0x14f, 0x150, 0x151, 0x152, 0x153, 0x154, 0x155, 0x156, 0x157, 0x158, 0x159, 0x15a, 0x15b, 0x15c, 0x15d, 0x15e, 0x15f, 0x160, 0x161, 0x162, 0x163, 0x164, 0x165, 0x166, 0x167, 0x168, 0x169, 0x16a, 0x16b, 0x16c, 0x16d, 0x16e, 0x16f, 0x170, 0x171, 0x172, 0x173, 0x174, 0x175, 0x176, 0x177, 0x178, 0x179, 0x17a, 0x17b, 0x17c, 0x17d, 0x17e, 0x17f, 0x180, 0x181, 0x182, 0x183, 0x184, 0x185, 0x186, 0x187, 0x188, 0x189, 0x18a, 0x18b, 0x18c, 0x18d, 0x18e, 0x18f, 0x190, 0x191, 0x192, 0x193, 0x194, 0x195, 0x196, 0x197, 0x198, 0x199, 0x19a, 0x19b, 0x19c, 0x19d, 0x19e, 0x19f, 0x1a0, 0x1a1, 0x1a2, 0x1a3, 0x1a4, 0x1a5, 0x1a6, 0x1a7, 0x1a8, 0x1a9, 0x1aa, 0x1ab, 0x1ac, 0x1ad, 0x1ae, 0x1af, 0x1b0, 0x1b1, 0x1b2, 0x1b3, 0x1b4, 0x1b5, 0x1b6, 0x1b7, 0x1b8, 0x1b9, 0x1ba, 0x1bb, 0x1bc, 0x1bd, 0x1be, 0x1bf, 0x1c0, 0x1c1, 0x1c2, 0x1c3, 0x1c4, 0x1c5, 0x1c6, 0x1c7, 0x1c8, 0x1c9, 0x1ca, 0x1cb, 0x1cc, 0x1cd, 0x1ce, 0x1cf, 0x1d0, 0x1d1, 0x1d2, 0x1d3, 0x1d4, 0x1d5, 0x1d6, 0x1d7, 0x1d8, 0x1d9, 0x1da, 0x1db, 0x1dc, 0x1dd, 0x1de, 0x1df, 0x1e0, 0x1e1, 0x1e2, 0x1e3, 0x1e4, 0x1e5, 0x1e6, 0x1e7, 0x1e8, 0x1e9, 0x1ea, 0x1eb, 0x1ec, 0x1ed, 0x1ee, 0x1ef, 0x1f0, 0x1f1, 0x1f2, 0x1f3, 0x1f4, 0x1f5, 0x1f6, 0x1f7, 0x1f8, 0x1f9, 0x1fa, 0x1fb, 0x1fc, 0x1fd, 0x1fe, 0x1ff, 0x200, 0x201, 0x202, 0x203, 0x204, 0x205, 0x206, 0x207, 0x208, 0x209, 0x20a, 0x20b, 0x20c, 0x20d, 0x20e, 0x20f, 0x210, 0x211, 0x212, 0x213, 0x214, 0x215, 0x216, 0x217, 0x218, 0x219, 0x21a, 0x21b, 0x21c, 0x21d, 0x21e, 0x21f, 0x220, 0x221, 0x222, 0x223, 0x224, 0x225, 0x226, 0x227, 0x228, 0x229, 0x22a, 0x22b, 0x22c, 0x22d, 0x22e, 0x22f, 0x230, 0x231, 0x232, 0x233, 0x234, 0x235, 0x236, 0x237, 0x238, 0x239, 0x23a, 0x23b, 0x23c, 0x23d, 0x23e, 0x23f, 0x240, 0x241, 0x242, 0x243, 0x244, 0x245, 0x246, 0x247, 0x248, 0x249, 0x24a, 0x24b, 0x24c, 0x24d, 0x24e, 0x24f, 0x250, 0x251, 0x252, 0x253, 0x254, 0x255, 0x256, 0x257, 0x258, 0x259, 0x25a, 0x25b, 0x25c, 0x25d, 0x25e, 0x25f, 0x260, 0x261, 0x262, 0x263, 0x264, 0x265, 0x266, 0x267, 0x268, 0x269, 0x26a, 0x26b, 0x26c, 0x26d, 0x26e, 0x26f, 0x270, 0x271, 0x272, 0x273, 0x274, 0x275, 0x276, 0x277, 0x278, 0x279, 0x27a, 0x27b, 0x27c, 0x27d, 0x27e, 0x27f, 0x280, 0x281, 0x282, 0x283, 0x284, 0x285, 0x286, 0x287, 0x288, 0x289, 0x28a, 0x28b, 0x28c, 0x28d, 0x28e, 0x28f, 0x290, 0x291, 0x292, 0x293, 0x294, 0x295, 0x296, 0x297, 0x298, 0x299, 0x29a, 0x29b, 0x29c, 0x29d, 0x29e, 0x29f, 0x2a0, 0x2a1, 0x2a2, 0x2a3, 0x2a4, 0x2a5, 0x2a6, 0x2a7, 0x2a8, 0x2a9, 0x2aa, 0x2ab, 0x2ac, 0x2ad, 0x2ae, 0x2af, 0x2b0, 0x2b1, 0x2b2, 0x2b3, 0x2b4, 0x2b5, 0x2b6, 0x2b7, 0x2b8, 0x2b9, 0x2ba, 0x2bb, 0x2bc, 0x2bd, 0x2be, 0x2bf, 0x2c0, 0x2c1, 0x2c2, 0x2c3, 0x2c4, 0x2c5, 0x2c6, 0x2c7, 0x2c8, 0x2c9, 0x2ca, 0x2cb, 0x2cc, 0x2cd, 0x2ce, 0x2cf, 0x2d0, 0x2d1, 0x2d2, 0x2d3, 0x2d4, 0x2d5, 0x2d6, 0x2d7, 0x2d8, 0x2d9, 0x2da, 0x2db, 0x2dc, 0x2dd, 0x2de, 0x2df, 0x2e0, 0x2e1, 0x2e2, 0x2e3, 0x2e4, 0x2e5, 0x2e6, 0x2e7, 0x2e8, 0x2e9, 0x2ea, 0x2eb, 0x2ec, 0x2ed, 0x2ee, 0x2ef, 0x2f0, 0x2f1, 0x2f2, 0x2f3, 0x2f4, 0x2f5, 0x2f6, 0x2f7, 0x2f8, 0x2f9, 0x2fa, 0x2fb, 0x2fc, 0x2fd, 0x2fe, 0x2ff, 0x300, 0x301, 0x302, 0x303, 0x304, 0x305, 0x306, 0x307, 0x308, 0x309, 0x30a, 0x30b, 0x30c, 0x30d, 0x30e, 0x30f, 0x310, 0x311, 0x312, 0x313, 0x314, 0x315, 0x316, 0x317, 0x318, 0x319, 0x31a, 0x31b, 0x31c, 0x31d, 0x31e, 0x31f, 0x320, 0x321, 0x322, 0x323, 0x324, 0x325, 0x326, 0x327, 0x328, 0x329, 0x32a, 0x32b, 0x32c, 0x32d, 0x32e, 0x32f, 0x330, 0x331, 0x332, 0x333, 0x334, 0x335, 0x336, 0x337, 0x338, 0x339, 0x33a, 0x33b, 0x33c, 0x33d, 0x33e, 0x33f, 0x340, 0x341, 0x342, 0x343, 0x344, 0x345, 0x346, 0x347, 0x348, 0x349, 0x34a, 0x34b, 0x34c, 0x34d, 0x34e, 0x34f, 0x350, 0x351, 0x352, 0x353, 0x354, 0x355, 0x356, 0x357, 0x358, 0x359, 0x35a, 0x35b, 0x35c, 0x35d, 0x35e, 0x35f, 0x360, 0x361, 0x362, 0x363, 0x364, 0x365, 0x366, 0x367, 0x368, 0x369, 0x36a, 0x36b, 0x36c, 0x36d, 0x36e, 0x36f, 0x370, 0x371, 0x372, 0x373, 0x374, 0x375, 0x376, 0x377, 0x378, 0x379, 0x37a, 0x37b, 0x37c, 0x37d, 0x37e, 0x37f, 0x380, 0x381, 0x382, 0x383, 0x384, 0x385, 0x386, 0x387, 0x388, 0x389, 0x38a, 0x38b, 0x38c, 0x38d, 0x38e, 0x38f, 0x390, 0x391, 0x392, 0x393, 0x394, 0x395, 0x396, 0x397, 0x398, 0x399, 0x39a, 0x39b, 0x39c, 0x39d, 0x39e, 0x39f, 0x3a0, 0x3a1, 0x3a2, 0x3a3, 0x3a4, 0x3a5, 0x3a6, 0x3a7, 0x3a8, 0x3a9, 0x3aa, 0x3ab, 0x3ac, 0x3ad, 0x3ae, 0x3af, 0x3b0, 0x3b1, 0x3b2, 0x3b3, 0x3b4, 0x3b5, 0x3b6, 0x3b7, 0x3b8, 0x3b9, 0x3ba, 0x3bb, 0x3bc, 0x3bd, 0x3be, 0x3bf, 0x3c0, 0x3c1, 0x3c2, 0x3c3, 0x3c4, 0x3c5, 0x3c6, 0x3c7, 0x3c8, 0x3c9, 0x3ca, 0x3cb, 0x3cc, 0x3cd, 0x3ce, 0x3cf, 0x3d0, 0x3d1, 0x3d2, 0x3d3, 0x3d4, 0x3d5, 0x3d6, 0x3d7, 0x3d8, 0x3d9, 0x3da, 0x3db, 0x3dc, 0x3dd, 0x3de, 0x3df, 0x3e0, 0x3e1, 0x3e2, 0x3e3, 0x3e4, 0x3e5, 0x3e6, 0x3e7, 0x3e8, 0x3e9, 0x3ea, 0x3eb, 0x3ec, 0x3ed, 0x3ee, 0x3ef, 0x3f0, 0x3f1, 0x3f2, 0x3f3, 0x3f4, 0x3f5, 0x3f6, 0x3f7, 0x3f8, 0x3f9, 0x3fa, 0x3fb, 0x3fc, 0x3fd, 0x3fe, 0x3ff, 0x400, 0x401, 0x402, 0x403, 0x404, 0x405, 0x406, 0x407, 0x408, 0x409, 0x40a, 0x40b, 0x40c, 0x40d, 0x40e, 0x40f, 0x410, 0x411, 0x412, 0x413, 0x414, 0x415, 0x416, 0x417, 0x418, 0x419, 0x41a, 0x41b, 0x41c, 0x41d, 0x41e, 0x41f, 0x420, 0x421, 0x422, 0x423, 0x424, 0x425, 0x426, 0x427, 0x428, 0x429, 0x42a, 0x42b, 0x42c, 0x42d, 0x42e, 0x42f, 0x430, 0x431, 0x432, 0x433, 0x434, 0x435, 0x436, 0x437, 0x438, 0x439, 0x43a, 0x43b, 0x43c, 0x43d, 0x43e, 0x43f, 0x440, 0x441, 0x442, 0x443, 0x444, 0x445, 0x446, 0x447, 0x448, 0x449, 0x44a, 0x44b, 0x44c, 0x44d, 0x44e, 0x44f, 0x450, 0x451, 0x452, 0x453, 0x454, 0x455, 0x456, 0x457, 0x458, 0x459, 0x45a, 0x45b, 0x45c, 0x45d, 0x45e, 0x45f, 0x460, 0x461, 0x462, 0x463, 0x464, 0x465, 0x466, 0x467, 0x468, 0x469, 0x46a, 0x46b, 0x46c, 0x46d, 0x46e, 0x46f, 0x470, 0x471, 0x472, 0x473, 0x474, 0x475, 0x476, 0x477, 0x478, 0x479, 0x47a, 0x47b, 0x47c, 0x47d, 0x47e, 0x47f, 0x480, 0x481, 0x482, 0x483, 0x484, 0x485, 0x486, 0x487, 0x488, 0x489, 0x48a, 0x48b, 0x48c, 0x48d, 0x48e, 0x48f, 0x490, 0x491, 0x492, 0x493, 0x494, 0x495, 0x496, 0x497, 0x498, 0x499, 0x49a, 0x49b, 0x49c, 0x49d, 0x49e, 0x49f, 0x4a0, 0x4a1, 0x4a2, 0x4a3, 0x4a4, 0x4a5, 0x4a6, 0x4a7, 0x4a8, 0x4a9, 0x4aa, 0x4ab, 0x4ac, 0x4ad, 0x4ae, 0x4af, 0x4b0, 0x4b1, 0x4b2, 0x4b3, 0x4b4, 0x4b5, 0x4b6, 0x4b7, 0x4b8, 0x4b9, 0x4ba, 0x4bb, 0x4bc, 0x4bd, 0x4be, 0x4bf, 0x4c0, 0x4c1, 0x4c2, 0x4c3, 0x4c4, 0x4c5, 0x4c6, 0x4c7, 0x4c8, 0x4c9, 0x4ca, 0x4cb, 0x4cc, 0x4cd, 0x4ce, 0x4cf, 0x4d0, 0x4d1, 0x4d2, 0x4d3, 0x4d4, 0x4d5, 0x4d6, 0x4d7, 0x4d8, 0x4d9, 0x4da, 0x4db, 0x4dc, 0x4dd, 0x4de, 0x4df, 0x4e0, 0x4e1, 0x4e2, 0x4e3, 0x4e4, 0x4e5, 0x4e6, 0x4e7, 0x4e8, 0x4e9, 0x4ea, 0x4eb, 0x4ec, 0x4ed, 0x4ee, 0x4ef, 0x4f0, 0x4f1, 0x4f2, 0x4f3, 0x4f4, 0x4f5, 0x4f6, 0x4f7, 0x4f8, 0x4f9, 0x4fa, 0x4fb, 0x4fc, 0x4fd, 0x4fe, 0x4ff, 0x500, 0x501, 0x502, 0x503, 0x504, 0x505, 0x506, 0x507, 0x508, 0x509, 0x50a, 0x50b, 0x50c, 0x50d, 0x50e, 0x50f, 0x510, 0x511, 0x512, 0x513, 0x514, 0x515, 0x516, 0x517, 0x518, 0x519, 0x51a, 0x51b, 0x51c, 0x51d, 0x51e, 0x51f, 0x520, 0x521, 0x522, 0x523, 0x524, 0x525, 0x526, 0x527, 0x528, 0x529, 0x52a, 0x52b, 0x52c, 0x52d, 0x52e, 0x52f, 0x530, 0x531, 0x532, 0x533, 0x534, 0x535, 0x536, 0x537, 0x538, 0x539, 0x53a, 0x53b, 0x53c, 0x53d, 0x53e, 0x53f, 0x540, 0x541, 0x542, 0x543, 0x544, 0x545, 0x546, 0x547, 0x548, 0x549, 0x54a, 0x54b, 0x54c, 0x54d, 0x54e, 0x54f, 0x550, 0x551, 0x552, 0x553, 0x554, 0x555, 0x556, 0x557, 0x558, 0x559, 0x55a, 0x55b, 0x55c, 0x55d, 0x55e, 0x55f, 0x560, 0x561, 0x562, 0x563, 0x564, 0x565, 0x566, 0x567, 0x568, 0x569, 0x56a, 0x56b, 0x56c, 0x56d, 0x56e, 0x56f, 0x570, 0x571, 0x572, 0x573, 0x574, 0x575, 0x576, 0x577, 0x578, 0x579, 0x57a, 0x57b, 0x57c, 0x57d, 0x57e, 0x57f, 0x580, 0x581, 0x582, 0x583, 0x584, 0x585, 0x586, 0x587, 0x588, 0x589, 0x58a, 0x58b, 0x58c, 0x58d, 0x58e, 0x58f, 0x590, 0x591, 0x592, 0x593, 0x594, 0x595, 0x596, 0x597, 0x598, 0x599, 0x59a, 0x59b, 0x59c, 0x59d, 0x59e, 0x59f, 0x5a0, 0x5a1, 0x5a2, 0x5a3, 0x5a4, 0x5a5, 0x5a6, 0x5a7, 0x5a8, 0x5a9, 0x5aa, 0x5ab, 0x5ac, 0x5ad, 0x5ae, 0x5af, 0x5b0, 0x5b1, 0x5b2, 0x5b3, 0x5b4, 0x5b5, 0x5b6, 0x5b7, 0x5b8, 0x5b9, 0x5ba, 0x5bb, 0x5bc, 0x5bd, 0x5be, 0x5bf, 0x5c0, 0x5c1, 0x5c2, 0x5c3, 0x5c4, 0x5c5, 0x5c6, 0x5c7, 0x5c8, 0x5c9, 0x5ca, 0x5cb, 0x5cc, 0x5cd, 0x5ce, 0x5cf, 0x5d0, 0x5d1, 0x5d2, 0x5d3, 0x5d4, 0x5d5, 0x5d6, 0x5d7, 0x5d8, 0x5d9, 0x5da, 0x5db, 0x5dc, 0x5dd, 0x5de, 0x5df, 0x5e0, 0x5e1, 0x5e2, 0x5e3, 0x5e4, 0x5e5, 0x5e6, 0x5e7, 0x5e8, 0x5e9, 0x5ea, 0x5eb, 0x5ec, 0x5ed, 0x5ee, 0x5ef, 0x5f0, 0x5f1, 0x5f2, 0x5f3, 0x5f4, 0x5f5, 0x5f6, 0x5f7, 0x5f8, 0x5f9, 0x5fa, 0x5fb, 0x5fc, 0x5fd, 0x5fe, 0x5ff, 0x600, 0x601, 0x602, 0x603, 0x604, 0x605, 0x606, 0x607, 0x608, 0x609, 0x60a, 0x60b, 0x60c, 0x60d, 0x60e, 0x60f, 0x610, 0x611, 0x612, 0x613, 0x614, 0x615, 0x616, 0x617, 0x618, 0x619, 0x61a, 0x61b, 0x61c, 0x61d, 0x61e, 0x61f, 0x620, 0x621, 0x622, 0x623, 0x624, 0x625, 0x626, 0x627, 0x628, 0x629, 0x62a, 0x62b, 0x62c, 0x62d, 0x62e, 0x62f, 0x630, 0x631, 0x632, 0x633, 0x634, 0x635, 0x636, 0x637, 0x638, 0x639, 0x63a, 0x63b, 0x63c, 0x63d, 0x63e, 0x63f, 0x640, 0x641, 0x642, 0x643, 0x644, 0x645, 0x646, 0x647, 0x648, 0x649, 0x64a, 0x64b, 0x64c, 0x64d, 0x64e, 0x64f, 0x650, 0x651, 0x652, 0x653, 0x654, 0x655, 0x656, 0x657, 0x658, 0x659, 0x65a, 0x65b, 0x65c, 0x65d, 0x65e, 0x65f, 0x660, 0x661, 0x662, 0x663, 0x664, 0x665, 0x666, 0x667, 0x668, 0x669, 0x66a, 0x66b, 0x66c, 0x66d, 0x66e, 0x66f, 0x670, 0x671, 0x672, 0x673, 0x674, 0x675, 0x676, 0x677, 0x678, 0x679, 0x67a, 0x67b, 0x67c, 0x67d, 0x67e, 0x67f, 0x680, 0x681, 0x682, 0x683, 0x684, 0x685, 0x686, 0x687, 0x688, 0x689, 0x68a, 0x68b, 0x68c, 0x68d, 0x68e, 0x68f, 0x690, 0x691, 0x692, 0x693, 0x694, 0x695, 0x696, 0x697, 0x698, 0x699, 0x69a, 0x69b, 0x69c, 0x69d, 0x69e, 0x69f, 0x6a0, 0x6a1, 0x6a2, 0x6a3, 0x6a4, 0x6a5, 0x6a6, 0x6a7, 0x6a8, 0x6a9, 0x6aa, 0x6ab, 0x6ac, 0x6ad, 0x6ae, 0x6af, 0x6b0, 0x6b1, 0x6b2, 0x6b3, 0x6b4, 0x6b5, 0x6b6, 0x6b7, 0x6b8, 0x6b9, 0x6ba, 0x6bb, 0x6bc, 0x6bd, 0x6be, 0x6bf, 0x6c0, 0x6c1, 0x6c2, 0x6c3, 0x6c4, 0x6c5, 0x6c6, 0x6c7, 0x6c8, 0x6c9, 0x6ca, 0x6cb, 0x6cc, 0x6cd, 0x6ce, 0x6cf, 0x6d0, 0x6d1, 0x6d2, 0x6d3, 0x6d4, 0x6d5, 0x6d6, 0x6d7, 0x6d8, 0x6d9, 0x6da, 0x6db, 0x6dc, 0x6dd, 0x6de, 0x6df, 0x6e0, 0x6e1, 0x6e2, 0x6e3, 0x6e4, 0x6e5, 0x6e6, 0x6e7, 0x6e8, 0x6e9, 0x6ea, 0x6eb, 0x6ec, 0x6ed, 0x6ee, 0x6ef, 0x6f0, 0x6f1, 0x6f2, 0x6f3, 0x6f4, 0x6f5, 0x6f6, 0x6f7, 0x6f8, 0x6f9, 0x6fa, 0x6fb, 0x6fc, 0x6fd, 0x6fe, 0x6ff, 0x700, 0x701, 0x702, 0x703, 0x704, 0x705, 0x706, 0x707, 0x708, 0x709, 0x70a, 0x70b, 0x70c, 0x70d, 0x70e, 0x70f, 0x710, 0x711, 0x712, 0x713, 0x714, 0x715, 0x716, 0x717, 0x718, 0x719, 0x71a, 0x71b, 0x71c, 0x71d, 0x71e, 0x71f, 0x720, 0x721, 0x722, 0x723, 0x724, 0x725, 0x726, 0x727, 0x728, 0x729, 0x72a, 0x72b, 0x72c, 0x72d, 0x72e, 0x72f, 0x730, 0x731, 0x732, 0x733, 0x734, 0x735, 0x736, 0x737, 0x738, 0x739, 0x73a, 0x73b, 0x73c, 0x73d, 0x73e, 0x73f, 0x740, 0x741, 0x742, 0x743, 0x744, 0x745, 0x746, 0x747, 0x748, 0x749, 0x74a, 0x74b, 0x74c, 0x74d, 0x74e, 0x74f, 0x750, 0x751, 0x752, 0x753, 0x754, 0x755, 0x756, 0x757, 0x758, 0x759, 0x75a, 0x75b, 0x75c, 0x75d, 0x75e, 0x75f, 0x760, 0x761, 0x762, 0x763, 0x764, 0x765, 0x766, 0x767, 0x768, 0x769, 0x76a, 0x76b, 0x76c, 0x76d, 0x76e, 0x76f, 0x770, 0x771, 0x772, 0x773, 0x774, 0x775, 0x776, 0x777, 0x778, 0x779, 0x77a, 0x77b, 0x77c, 0x77d, 0x77e, 0x77f, 0x780, 0x781, 0x782, 0x783, 0x784, 0x785, 0x786, 0x787, 0x788, 0x789, 0x78a, 0x78b, 0x78c, 0x78d, 0x78e, 0x78f, 0x790, 0x791, 0x792, 0x793, 0x794, 0x795, 0x796, 0x797, 0x798, 0x799, 0x79a, 0x79b, 0x79c, 0x79d, 0x79e, 0x79f, 0x7a0, 0x7a1, 0x7a2, 0x7a3, 0x7a4, 0x7a5, 0x7a6, 0x7a7, 0x7a8, 0x7a9, 0x7aa, 0x7ab, 0x7ac, 0x7ad, 0x7ae, 0x7af, 0x7b0, 0x7b1, 0x7b2, 0x7b3, 0x7b4, 0x7b5, 0x7b6, 0x7b7, 0x7b8, 0x7b9, 0x7ba, 0x7bb, 0x7bc, 0x7bd, 0x7be, 0x7bf, 0x7c0, 0x7c1, 0x7c2, 0x7c3, 0x7c4, 0x7c5, 0x7c6, 0x7c7, 0x7c8, 0x7c9, 0x7ca, 0x7cb, 0x7cc, 0x7cd, 0x7ce, 0x7cf, 0x7d0, 0x7d1, 0x7d2, 0x7d3, 0x7d4, 0x7d5, 0x7d6, 0x7d7, 0x7d8, 0x7d9, 0x7da, 0x7db, 0x7dc, 0x7dd, 0x7de, 0x7df, 0x7e0, 0x7e1, 0x7e2, 0x7e3, 0x7e4, 0x7e5, 0x7e6, 0x7e7, 0x7e8, 0x7e9, 0x7ea, 0x7eb, 0x7ec, 0x7ed, 0x7ee, 0x7ef, 0x7f0, 0x7f1, 0x7f2, 0x7f3, 0x7f4, 0x7f5, 0x7f6, 0x7f7, 0x7f8, 0x7f9, 0x7fa, 0x7fb, 0x7fc, 0x7fd, 0x7fe, 0x7ff, 0x800, 0x801, 0x802, 0x803, 0x804, 0x805, 0x806, 0x807, 0x808, 0x809, 0x80a, 0x80b, 0x80c, 0x80d, 0x80e, 0x80f, 0x810, 0x811, 0x812, 0x813, 0x814, 0x815, 0x816, 0x817, 0x818, 0x819, 0x81a, 0x81b, 0x81c, 0x81d, 0x81e, 0x81f, 0x820, 0x821, 0x822, 0x823, 0x824, 0x825, 0x826, 0x827, 0x828, 0x829, 0x82a, 0x82b, 0x82c, 0x82d, 0x82e, 0x82f, 0x830, 0x831, 0x832, 0x833, 0x834, 0x835, 0x836, 0x837, 0x838, 0x839, 0x83a, 0x83b, 0x83c, 0x83d, 0x83e, 0x83f, 0x840, 0x841, 0x842, 0x843, 0x844, 0x845, 0x846, 0x847, 0x848, 0x849, 0x84a, 0x84b, 0x84c, 0x84d, 0x84e, 0x84f, 0x850, 0x851, 0x852, 0x853, 0x854, 0x855, 0x856, 0x857, 0x858, 0x859, 0x85a, 0x85b, 0x85c, 0x85d, 0x85e, 0x85f, 0x860, 0x861, 0x862, 0x863, 0x864, 0x865, 0x866, 0x867, 0x868, 0x869, 0x86a, 0x86b, 0x86c, 0x86d, 0x86e, 0x86f, 0x870, 0x871, 0x872, 0x873, 0x874, 0x875, 0x876, 0x877, 0x878, 0x879, 0x87a, 0x87b, 0x87c, 0x87d, 0x87e, 0x87f, 0x880, 0x881, 0x882, 0x883, 0x884, 0x885, 0x886, 0x887, 0x888, 0x889, 0x88a, 0x88b, 0x88c, 0x88d, 0x88e, 0x88f, 0x890, 0x891, 0x892, 0x893, 0x894, 0x895, 0x896, 0x897, 0x898, 0x899, 0x89a, 0x89b, 0x89c, 0x89d, 0x89e, 0x89f, 0x8a0, 0x8a1, 0x8a2, 0x8a3, 0x8a4, 0x8a5, 0x8a6, 0x8a7, 0x8a8, 0x8a9, 0x8aa, 0x8ab, 0x8ac, 0x8ad, 0x8ae, 0x8af, 0x8b0, 0x8b1, 0x8b2, 0x8b3, 0x8b4, 0x8b5, 0x8b6, 0x8b7, 0x8b8, 0x8b9, 0x8ba, 0x8bb, 0x8bc, 0x8bd, 0x8be, 0x8bf, 0x8c0, 0x8c1, 0x8c2, 0x8c3, 0x8c4, 0x8c5, 0x8c6, 0x8c7, 0x8c8, 0x8c9, 0x8ca, 0x8cb, 0x8cc, 0x8cd, 0x8ce, 0x8cf, 0x8d0, 0x8d1, 0x8d2, 0x8d3, 0x8d4, 0x8d5, 0x8d6, 0x8d7, 0x8d8, 0x8d9, 0x8da, 0x8db, 0x8dc, 0x8dd, 0x8de, 0x8df, 0x8e0, 0x8e1, 0x8e2, 0x8e3, 0x8e4, 0x8e5, 0x8e6, 0x8e7, 0x8e8, 0x8e9, 0x8ea, 0x8eb, 0x8ec, 0x8ed, 0x8ee, 0x8ef, 0x8f0, 0x8f1, 0x8f2, 0x8f3, 0x8f4, 0x8f5, 0x8f6, 0x8f7, 0x8f8, 0x8f9, 0x8fa, 0x8fb, 0x8fc, 0x8fd, 0x8fe, 0x8ff, 0x900, 0x901, 0x902, 0x903, 0x904, 0x905, 0x906, 0x907, 0x908, 0x909, 0x90a, 0x90b, 0x90c, 0x90d, 0x90e, 0x90f, 0x910, 0x911, 0x912, 0x913, 0x914, 0x915, 0x916, 0x917, 0x918, 0x919, 0x91a, 0x91b, 0x91c, 0x91d, 0x91e, 0x91f, 0x920, 0x921, 0x922, 0x923, 0x924, 0x925, 0x926, 0x927, 0x928, 0x929, 0x92a, 0x92b, 0x92c, 0x92d, 0x92e, 0x92f, 0x930, 0x931, 0x932, 0x933, 0x934, 0x935, 0x936, 0x937, 0x938, 0x939, 0x93a, 0x93b, 0x93c, 0x93d, 0x93e, 0x93f, 0x940, 0x941, 0x942, 0x943, 0x944, 0x945, 0x946, 0x947, 0x948, 0x949, 0x94a, 0x94b, 0x94c, 0x94d, 0x94e, 0x94f, 0x950, 0x951, 0x952, 0x953, 0x954, 0x955, 0x956, 0x957, 0x958, 0x959, 0x95a, 0x95b, 0x95c, 0x95d, 0x95e, 0x95f, 0x960, 0x961, 0x962, 0x963, 0x964, 0x965, 0x966, 0x967, 0x968, 0x969, 0x96a, 0x96b, 0x96c, 0x96d, 0x96e, 0x96f, 0x970, 0x971, 0x972, 0x973, 0x974, 0x975, 0x976, 0x977, 0x978, 0x979, 0x97a, 0x97b, 0x97c, 0x97d, 0x97e, 0x97f, 0x980, 0x981, 0x982, 0x983, 0x984, 0x985, 0x986, 0x987, 0x988, 0x989, 0x98a, 0x98b, 0x98c, 0x98d, 0x98e, 0x98f, 0x990, 0x991, 0x992, 0x993, 0x994, 0x995, 0x996, 0x997, 0x998, 0x999, 0x99a, 0x99b, 0x99c, 0x99d, 0x99e, 0x99f, 0x9a0, 0x9a1, 0x9a2, 0x9a3, 0x9a4, 0x9a5, 0x9a6, 0x9a7, 0x9a8, 0x9a9, 0x9aa, 0x9ab, 0x9ac, 0x9ad, 0x9ae, 0x9af, 0x9b0, 0x9b1, 0x9b2, 0x9b3, 0x9b4, 0x9b5, 0x9b6, 0x9b7, 0x9b8, 0x9b9, 0x9ba, 0x9bb, 0x9bc, 0x9bd, 0x9be, 0x9bf, 0x9c0, 0x9c1, 0x9c2, 0x9c3, 0x9c4, 0x9c5, 0x9c6, 0x9c7, 0x9c8, 0x9c9, 0x9ca, 0x9cb, 0x9cc, 0x9cd, 0x9ce, 0x9cf, 0x9d0, 0x9d1, 0x9d2, 0x9d3, 0x9d4, 0x9d5, 0x9d6, 0x9d7, 0x9d8, 0x9d9, 0x9da, 0x9db, 0x9dc, 0x9dd, 0x9de, 0x9df, 0x9e0, 0x9e1, 0x9e2, 0x9e3, 0x9e4, 0x9e5, 0x9e6, 0x9e7, 0x9e8, 0x9e9, 0x9ea, 0x9eb, 0x9ec, 0x9ed, 0x9ee, 0x9ef, 0x9f0, 0x9f1, 0x9f2, 0x9f3, 0x9f4, 0x9f5, 0x9f6, 0x9f7, 0x9f8, 0x9f9, 0x9fa, 0x9fb, 0x9fc, 0x9fd, 0x9fe, 0x9ff, 0xa00, 0xa01, 0xa02, 0xa03, 0xa04, 0xa05, 0xa06, 0xa07, 0xa08, 0xa09, 0xa0a, 0xa0b, 0xa0c, 0xa0d, 0xa0e, 0xa0f, 0xa10, 0xa11, 0xa12, 0xa13, 0xa14, 0xa15, 0xa16, 0xa17, 0xa18, 0xa19, 0xa1a, 0xa1b, 0xa1c, 0xa1d, 0xa1e, 0xa1f, 0xa20, 0xa21, 0xa22, 0xa23, 0xa24, 0xa25, 0xa26, 0xa27, 0xa28, 0xa29, 0xa2a, 0xa2b, 0xa2c, 0xa2d, 0xa2e, 0xa2f, 0xa30, 0xa31, 0xa32, 0xa33, 0xa34, 0xa35, 0xa36, 0xa37, 0xa38, 0xa39, 0xa3a, 0xa3b, 0xa3c, 0xa3d, 0xa3e, 0xa3f, 0xa40, 0xa41, 0xa42, 0xa43, 0xa44, 0xa45, 0xa46, 0xa47, 0xa48, 0xa49, 0xa4a, 0xa4b, 0xa4c, 0xa4d, 0xa4e, 0xa4f, 0xa50, 0xa51, 0xa52, 0xa53, 0xa54, 0xa55, 0xa56, 0xa57, 0xa58, 0xa59, 0xa5a, 0xa5b, 0xa5c, 0xa5d, 0xa5e, 0xa5f, 0xa60, 0xa61, 0xa62, 0xa63, 0xa64, 0xa65, 0xa66, 0xa67, 0xa68, 0xa69, 0xa6a, 0xa6b, 0xa6c, 0xa6d, 0xa6e, 0xa6f, 0xa70, 0xa71, 0xa72, 0xa73, 0xa74, 0xa75, 0xa76, 0xa77, 0xa78, 0xa79, 0xa7a, 0xa7b, 0xa7c, 0xa7d, 0xa7e, 0xa7f, 0xa80, 0xa81, 0xa82, 0xa83, 0xa84, 0xa85, 0xa86, 0xa87, 0xa88, 0xa89, 0xa8a, 0xa8b, 0xa8c, 0xa8d, 0xa8e, 0xa8f, 0xa90, 0xa91, 0xa92, 0xa93, 0xa94, 0xa95, 0xa96, 0xa97, 0xa98, 0xa99, 0xa9a, 0xa9b, 0xa9c, 0xa9d, 0xa9e, 0xa9f, 0xaa0, 0xaa1, 0xaa2, 0xaa3, 0xaa4, 0xaa5, 0xaa6, 0xaa7, 0xaa8, 0xaa9, 0xaaa, 0xaab, 0xaac, 0xaad, 0xaae, 0xaaf, 0xab0, 0xab1, 0xab2, 0xab3, 0xab4, 0xab5, 0xab6, 0xab7, 0xab8, 0xab9, 0xaba, 0xabb, 0xabc, 0xabd, 0xabe, 0xabf, 0xac0, 0xac1, 0xac2, 0xac3, 0xac4, 0xac5, 0xac6, 0xac7, 0xac8, 0xac9, 0xaca, 0xacb, 0xacc, 0xacd, 0xace, 0xacf, 0xad0, 0xad1, 0xad2, 0xad3, 0xad4, 0xad5, 0xad6, 0xad7, 0xad8, 0xad9, 0xada, 0xadb, 0xadc, 0xadd, 0xade, 0xadf, 0xae0, 0xae1, 0xae2, 0xae3, 0xae4, 0xae5, 0xae6, 0xae7, 0xae8, 0xae9, 0xaea, 0xaeb, 0xaec, 0xaed, 0xaee, 0xaef, 0xaf0, 0xaf1, 0xaf2, 0xaf3, 0xaf4, 0xaf5, 0xaf6, 0xaf7, 0xaf8, 0xaf9, 0xafa, 0xafb, 0xafc, 0xafd, 0xafe, 0xaff, 0xb00, 0xb01, 0xb02, 0xb03, 0xb04, 0xb05, 0xb06, 0xb07, 0xb08, 0xb09, 0xb0a, 0xb0b, 0xb0c, 0xb0d, 0xb0e, 0xb0f, 0xb10, 0xb11, 0xb12, 0xb13, 0xb14, 0xb15, 0xb16, 0xb17, 0xb18, 0xb19, 0xb1a, 0xb1b, 0xb1c, 0xb1d, 0xb1e, 0xb1f, 0xb20, 0xb21, 0xb22, 0xb23, 0xb24, 0xb25, 0xb26, 0xb27, 0xb28, 0xb29, 0xb2a, 0xb2b, 0xb2c, 0xb2d, 0xb2e, 0xb2f, 0xb30, 0xb31, 0xb32, 0xb33, 0xb34, 0xb35, 0xb36, 0xb37, 0xb38, 0xb39, 0xb3a, 0xb3b, 0xb3c, 0xb3d, 0xb3e, 0xb3f, 0xb40, 0xb41, 0xb42, 0xb43, 0xb44, 0xb45, 0xb46, 0xb47, 0xb48, 0xb49, 0xb4a, 0xb4b, 0xb4c, 0xb4d, 0xb4e, 0xb4f, 0xb50, 0xb51, 0xb52, 0xb53, 0xb54, 0xb55, 0xb56, 0xb57, 0xb58, 0xb59, 0xb5a, 0xb5b, 0xb5c, 0xb5d, 0xb5e, 0xb5f, 0xb60, 0xb61, 0xb62, 0xb63, 0xb64, 0xb65, 0xb66, 0xb67, 0xb68, 0xb69, 0xb6a, 0xb6b, 0xb6c, 0xb6d, 0xb6e, 0xb6f, 0xb70, 0xb71, 0xb72, 0xb73, 0xb74, 0xb75, 0xb76, 0xb77, 0xb78, 0xb79, 0xb7a, 0xb7b, 0xb7c, 0xb7d, 0xb7e, 0xb7f, 0xb80, 0xb81, 0xb82, 0xb83, 0xb84, 0xb85, 0xb86, 0xb87, 0xb88, 0xb89, 0xb8a, 0xb8b, 0xb8c, 0xb8d, 0xb8e, 0xb8f, 0xb90, 0xb91, 0xb92, 0xb93, 0xb94, 0xb95, 0xb96, 0xb97, 0xb98, 0xb99, 0xb9a, 0xb9b, 0xb9c, 0xb9d, 0xb9e, 0xb9f, 0xba0, 0xba1, 0xba2, 0xba3, 0xba4, 0xba5, 0xba6, 0xba7, 0xba8, 0xba9, 0xbaa, 0xbab, 0xbac, 0xbad, 0xbae, 0xbaf, 0xbb0, 0xbb1, 0xbb2, 0xbb3, 0xbb4, 0xbb5, 0xbb6, 0xbb7, 0xbb8, 0xbb9, 0xbba, 0xbbb, 0xbbc, 0xbbd, 0xbbe, 0xbbf, 0xbc0, 0xbc1, 0xbc2, 0xbc3, 0xbc4, 0xbc5, 0xbc6, 0xbc7, 0xbc8, 0xbc9, 0xbca, 0xbcb, 0xbcc, 0xbcd, 0xbce, 0xbcf, 0xbd0, 0xbd1, 0xbd2, 0xbd3, 0xbd4, 0xbd5, 0xbd6, 0xbd7, 0xbd8, 0xbd9, 0xbda, 0xbdb, 0xbdc, 0xbdd, 0xbde, 0xbdf, 0xbe0, 0xbe1, 0xbe2, 0xbe3, 0xbe4, 0xbe5, 0xbe6, 0xbe7, 0xbe8, 0xbe9, 0xbea, 0xbeb, 0xbec, 0xbed, 0xbee, 0xbef, 0xbf0, 0xbf1, 0xbf2, 0xbf3, 0xbf4, 0xbf5, 0xbf6, 0xbf7, 0xbf8, 0xbf9, 0xbfa, 0xbfb, 0xbfc, 0xbfd, 0xbfe, 0xbff, 0xc00, 0xc01, 0xc02, 0xc03, 0xc04, 0xc05, 0xc06, 0xc07, 0xc08, 0xc09, 0xc0a, 0xc0b, 0xc0c, 0xc0d, 0xc0e, 0xc0f, 0xc10, 0xc11, 0xc12, 0xc13, 0xc14, 0xc15, 0xc16, 0xc17, 0xc18, 0xc19, 0xc1a, 0xc1b, 0xc1c, 0xc1d, 0xc1e, 0xc1f, 0xc20, 0xc21, 0xc22, 0xc23, 0xc24, 0xc25, 0xc26, 0xc27, 0xc28, 0xc29, 0xc2a, 0xc2b, 0xc2c, 0xc2d, 0xc2e, 0xc2f, 0xc30, 0xc31, 0xc32, 0xc33, 0xc34, 0xc35, 0xc36, 0xc37, 0xc38, 0xc39, 0xc3a, 0xc3b, 0xc3c, 0xc3d, 0xc3e, 0xc3f, 0xc40, 0xc41, 0xc42, 0xc43, 0xc44, 0xc45, 0xc46, 0xc47, 0xc48, 0xc49, 0xc4a, 0xc4b, 0xc4c, 0xc4d, 0xc4e, 0xc4f, 0xc50, 0xc51, 0xc52, 0xc53, 0xc54, 0xc55, 0xc56, 0xc57, 0xc58, 0xc59, 0xc5a, 0xc5b, 0xc5c, 0xc5d, 0xc5e, 0xc5f, 0xc60, 0xc61, 0xc62, 0xc63, 0xc64, 0xc65, 0xc66, 0xc67, 0xc68, 0xc69, 0xc6a, 0xc6b, 0xc6c, 0xc6d, 0xc6e, 0xc6f, 0xc70, 0xc71, 0xc72, 0xc73, 0xc74, 0xc75, 0xc76, 0xc77, 0xc78, 0xc79, 0xc7a, 0xc7b, 0xc7c, 0xc7d, 0xc7e, 0xc7f, 0xc80, 0xc81, 0xc82, 0xc83, 0xc84, 0xc85, 0xc86, 0xc87, 0xc88, 0xc89, 0xc8a, 0xc8b, 0xc8c, 0xc8d, 0xc8e, 0xc8f, 0xc90, 0xc91, 0xc92, 0xc93, 0xc94, 0xc95, 0xc96, 0xc97, 0xc98, 0xc99, 0xc9a, 0xc9b, 0xc9c, 0xc9d, 0xc9e, 0xc9f, 0xca0, 0xca1, 0xca2, 0xca3, 0xca4, 0xca5, 0xca6, 0xca7, 0xca8, 0xca9, 0xcaa, 0xcab, 0xcac, 0xcad, 0xcae, 0xcaf, 0xcb0, 0xcb1, 0xcb2, 0xcb3, 0xcb4, 0xcb5, 0xcb6, 0xcb7, 0xcb8, 0xcb9, 0xcba, 0xcbb, 0xcbc, 0xcbd, 0xcbe, 0xcbf, 0xcc0, 0xcc1, 0xcc2, 0xcc3, 0xcc4, 0xcc5, 0xcc6, 0xcc7, 0xcc8, 0xcc9, 0xcca, 0xccb, 0xccc, 0xccd, 0xcce, 0xccf, 0xcd0, 0xcd1, 0xcd2, 0xcd3, 0xcd4, 0xcd5, 0xcd6, 0xcd7, 0xcd8, 0xcd9, 0xcda, 0xcdb, 0xcdc, 0xcdd, 0xcde, 0xcdf, 0xce0, 0xce1, 0xce2, 0xce3, 0xce4, 0xce5, 0xce6, 0xce7, 0xce8, 0xce9, 0xcea, 0xceb, 0xcec, 0xced, 0xcee, 0xcef, 0xcf0, 0xcf1, 0xcf2, 0xcf3, 0xcf4, 0xcf5, 0xcf6, 0xcf7, 0xcf8, 0xcf9, 0xcfa, 0xcfb, 0xcfc, 0xcfd, 0xcfe, 0xcff, 0xd00, 0xd01, 0xd02, 0xd03, 0xd04, 0xd05, 0xd06, 0xd07, 0xd08, 0xd09, 0xd0a, 0xd0b, 0xd0c, 0xd0d, 0xd0e, 0xd0f, 0xd10, 0xd11, 0xd12, 0xd13, 0xd14, 0xd15, 0xd16, 0xd17, 0xd18, 0xd19, 0xd1a, 0xd1b, 0xd1c, 0xd1d, 0xd1e, 0xd1f, 0xd20, 0xd21, 0xd22, 0xd23, 0xd24, 0xd25, 0xd26, 0xd27, 0xd28, 0xd29, 0xd2a, 0xd2b, 0xd2c, 0xd2d, 0xd2e, 0xd2f, 0xd30, 0xd31, 0xd32, 0xd33, 0xd34, 0xd35, 0xd36, 0xd37, 0xd38, 0xd39, 0xd3a, 0xd3b, 0xd3c, 0xd3d, 0xd3e, 0xd3f, 0xd40, 0xd41, 0xd42, 0xd43, 0xd44, 0xd45, 0xd46, 0xd47, 0xd48, 0xd49, 0xd4a, 0xd4b, 0xd4c, 0xd4d, 0xd4e, 0xd4f, 0xd50, 0xd51, 0xd52, 0xd53, 0xd54, 0xd55, 0xd56, 0xd57, 0xd58, 0xd59, 0xd5a, 0xd5b, 0xd5c, 0xd5d, 0xd5e, 0xd5f, 0xd60, 0xd61, 0xd62, 0xd63, 0xd64, 0xd65, 0xd66, 0xd67, 0xd68, 0xd69, 0xd6a, 0xd6b, 0xd6c, 0xd6d, 0xd6e, 0xd6f, 0xd70, 0xd71, 0xd72, 0xd73, 0xd74, 0xd75, 0xd76, 0xd77, 0xd78, 0xd79, 0xd7a, 0xd7b, 0xd7c, 0xd7d, 0xd7e, 0xd7f, 0xd80, 0xd81, 0xd82, 0xd83, 0xd84, 0xd85, 0xd86, 0xd87, 0xd88, 0xd89, 0xd8a, 0xd8b, 0xd8c, 0xd8d, 0xd8e, 0xd8f, 0xd90, 0xd91, 0xd92, 0xd93, 0xd94, 0xd95, 0xd96, 0xd97, 0xd98, 0xd99, 0xd9a, 0xd9b, 0xd9c, 0xd9d, 0xd9e, 0xd9f, 0xda0, 0xda1, 0xda2, 0xda3, 0xda4, 0xda5, 0xda6, 0xda7, 0xda8, 0xda9, 0xdaa, 0xdab, 0xdac, 0xdad, 0xdae, 0xdaf, 0xdb0, 0xdb1, 0xdb2, 0xdb3, 0xdb4, 0xdb5, 0xdb6, 0xdb7, 0xdb8, 0xdb9, 0xdba, 0xdbb, 0xdbc, 0xdbd, 0xdbe, 0xdbf, 0xdc0, 0xdc1, 0xdc2, 0xdc3, 0xdc4, 0xdc5, 0xdc6, 0xdc7, 0xdc8, 0xdc9, 0xdca, 0xdcb, 0xdcc, 0xdcd, 0xdce, 0xdcf, 0xdd0, 0xdd1, 0xdd2, 0xdd3, 0xdd4, 0xdd5, 0xdd6, 0xdd7, 0xdd8, 0xdd9, 0xdda, 0xddb, 0xddc, 0xddd, 0xdde, 0xddf, 0xde0, 0xde1, 0xde2, 0xde3, 0xde4, 0xde5, 0xde6, 0xde7, 0xde8, 0xde9, 0xdea, 0xdeb, 0xdec, 0xded, 0xdee, 0xdef, 0xdf0, 0xdf1, 0xdf2, 0xdf3, 0xdf4, 0xdf5, 0xdf6, 0xdf7, 0xdf8, 0xdf9, 0xdfa, 0xdfb, 0xdfc, 0xdfd, 0xdfe, 0xdff, 0xe00, 0xe01, 0xe02, 0xe03, 0xe04, 0xe05, 0xe06, 0xe07, 0xe08, 0xe09, 0xe0a, 0xe0b, 0xe0c, 0xe0d, 0xe0e, 0xe0f, 0xe10, 0xe11, 0xe12, 0xe13, 0xe14, 0xe15, 0xe16, 0xe17, 0xe18, 0xe19, 0xe1a, 0xe1b, 0xe1c, 0xe1d, 0xe1e, 0xe1f, 0xe20, 0xe21, 0xe22, 0xe23, 0xe24, 0xe25, 0xe26, 0xe27, 0xe28, 0xe29, 0xe2a, 0xe2b, 0xe2c, 0xe2d, 0xe2e, 0xe2f, 0xe30, 0xe31, 0xe32, 0xe33, 0xe34, 0xe35, 0xe36, 0xe37, 0xe38, 0xe39, 0xe3a, 0xe3b, 0xe3c, 0xe3d, 0xe3e, 0xe3f, 0xe40, 0xe41, 0xe42, 0xe43, 0xe44, 0xe45, 0xe46, 0xe47, 0xe48, 0xe49, 0xe4a, 0xe4b, 0xe4c, 0xe4d, 0xe4e, 0xe4f, 0xe50, 0xe51, 0xe52, 0xe53, 0xe54, 0xe55, 0xe56, 0xe57, 0xe58, 0xe59, 0xe5a, 0xe5b, 0xe5c, 0xe5d, 0xe5e, 0xe5f, 0xe60, 0xe61, 0xe62, 0xe63, 0xe64, 0xe65, 0xe66, 0xe67, 0xe68, 0xe69, 0xe6a, 0xe6b, 0xe6c, 0xe6d, 0xe6e, 0xe6f, 0xe70, 0xe71, 0xe72, 0xe73, 0xe74, 0xe75, 0xe76, 0xe77, 0xe78, 0xe79, 0xe7a, 0xe7b, 0xe7c, 0xe7d, 0xe7e, 0xe7f, 0xe80, 0xe81, 0xe82, 0xe83, 0xe84, 0xe85, 0xe86, 0xe87, 0xe88, 0xe89, 0xe8a, 0xe8b, 0xe8c, 0xe8d, 0xe8e, 0xe8f, 0xe90, 0xe91, 0xe92, 0xe93, 0xe94, 0xe95, 0xe96, 0xe97, 0xe98, 0xe99, 0xe9a, 0xe9b, 0xe9c, 0xe9d, 0xe9e, 0xe9f, 0xea0, 0xea1, 0xea2, 0xea3, 0xea4, 0xea5, 0xea6, 0xea7, 0xea8, 0xea9, 0xeaa, 0xeab, 0xeac, 0xead, 0xeae, 0xeaf, 0xeb0, 0xeb1, 0xeb2, 0xeb3, 0xeb4, 0xeb5, 0xeb6, 0xeb7, 0xeb8, 0xeb9, 0xeba, 0xebb, 0xebc, 0xebd, 0xebe, 0xebf, 0xec0, 0xec1, 0xec2, 0xec3, 0xec4, 0xec5, 0xec6, 0xec7, 0xec8, 0xec9, 0xeca, 0xecb, 0xecc, 0xecd, 0xece, 0xecf, 0xed0, 0xed1, 0xed2, 0xed3, 0xed4, 0xed5, 0xed6, 0xed7, 0xed8, 0xed9, 0xeda, 0xedb, 0xedc, 0xedd, 0xede, 0xedf, 0xee0, 0xee1, 0xee2, 0xee3, 0xee4, 0xee5, 0xee6, 0xee7, 0xee8, 0xee9, 0xeea, 0xeeb, 0xeec, 0xeed, 0xeee, 0xeef, 0xef0, 0xef1, 0xef2, 0xef3, 0xef4, 0xef5, 0xef6, 0xef7, 0xef8, 0xef9, 0xefa, 0xefb, 0xefc, 0xefd, 0xefe, 0xeff, 0xf00, 0xf01, 0xf02, 0xf03, 0xf04, 0xf05, 0xf06, 0xf07, 0xf08, 0xf09, 0xf0a, 0xf0b, 0xf0c, 0xf0d, 0xf0e, 0xf0f, 0xf10, 0xf11, 0xf12, 0xf13, 0xf14, 0xf15, 0xf16, 0xf17, 0xf18, 0xf19, 0xf1a, 0xf1b, 0xf1c, 0xf1d, 0xf1e, 0xf1f, 0xf20, 0xf21, 0xf22, 0xf23, 0xf24, 0xf25, 0xf26, 0xf27, 0xf28, 0xf29, 0xf2a, 0xf2b, 0xf2c, 0xf2d, 0xf2e, 0xf2f, 0xf30, 0xf31, 0xf32, 0xf33, 0xf34, 0xf35, 0xf36, 0xf37, 0xf38, 0xf39, 0xf3a, 0xf3b, 0xf3c, 0xf3d, 0xf3e, 0xf3f, 0xf40, 0xf41, 0xf42, 0xf43, 0xf44, 0xf45, 0xf46, 0xf47, 0xf48, 0xf49, 0xf4a, 0xf4b, 0xf4c, 0xf4d, 0xf4e, 0xf4f, 0xf50, 0xf51, 0xf52, 0xf53, 0xf54, 0xf55, 0xf56, 0xf57, 0xf58, 0xf59, 0xf5a, 0xf5b, 0xf5c, 0xf5d, 0xf5e, 0xf5f, 0xf60, 0xf61, 0xf62, 0xf63, 0xf64, 0xf65, 0xf66, 0xf67, 0xf68, 0xf69, 0xf6a, 0xf6b, 0xf6c, 0xf6d, 0xf6e, 0xf6f, 0xf70, 0xf71, 0xf72, 0xf73, 0xf74, 0xf75, 0xf76, 0xf77, 0xf78, 0xf79, 0xf7a, 0xf7b, 0xf7c, 0xf7d, 0xf7e, 0xf7f, 0xf80, 0xf81, 0xf82, 0xf83, 0xf84, 0xf85, 0xf86, 0xf87, 0xf88, 0xf89, 0xf8a, 0xf8b, 0xf8c, 0xf8d, 0xf8e, 0xf8f, 0xf90, 0xf91, 0xf92, 0xf93, 0xf94, 0xf95, 0xf96, 0xf97, 0xf98, 0xf99, 0xf9a, 0xf9b, 0xf9c, 0xf9d, 0xf9e, 0xf9f, 0xfa0, 0xfa1, 0xfa2, 0xfa3, 0xfa4, 0xfa5, 0xfa6, 0xfa7, 0xfa8, 0xfa9, 0xfaa, 0xfab, 0xfac, 0xfad, 0xfae, 0xfaf, 0xfb0, 0xfb1, 0xfb2, 0xfb3, 0xfb4, 0xfb5, 0xfb6, 0xfb7, 0xfb8, 0xfb9, 0xfba, 0xfbb, 0xfbc, 0xfbd, 0xfbe, 0xfbf, 0xfc0, 0xfc1, 0xfc2, 0xfc3, 0xfc4, 0xfc5, 0xfc6, 0xfc7, 0xfc8, 0xfc9, 0xfca, 0xfcb, 0xfcc, 0xfcd, 0xfce, 0xfcf, 0xfd0, 0xfd1, 0xfd2, 0xfd3, 0xfd4, 0xfd5, 0xfd6, 0xfd7, 0xfd8, 0xfd9, 0xfda, 0xfdb, 0xfdc, 0xfdd, 0xfde, 0xfdf, 0xfe0, 0xfe1, 0xfe2, 0xfe3, 0xfe4, 0xfe5, 0xfe6, 0xfe7, 0xfe8, 0xfe9, 0xfea, 0xfeb, 0xfec, 0xfed, 0xfee, 0xfef, 0xff0, 0xff1, 0xff2, 0xff3, 0xff4, 0xff5, 0xff6, 0xff7, 0xff8, 0xff9, 0xffa, 0xffb, 0xffc, 0xffd, 0xffe, 0xfff] cryptol-2.4.0/bench/data/SHA512.cry 0000644 0000000 0000000 00000010023 12737220176 014754 0 ustar 00 0000000 0000000 // Provided by @sdwelle as a performance regression in issue #269
module SHA512 where
sha512 : {b, a} (a*1024 == 128 + b + 1 + 1024 - (b+129) % 1024,
a*1024 % 1024 == 0,
a * 1024 - b >= 129,
2^^128 - 1 >= b,
fin (a + 1)) => [b] -> [512]
sha512 M = result
where
M' = (pad M)
blocks = (groupBy`{1024} M')
hash = [H0] # [ processBlock b h | b <- blocks | h <- hash ]
result = (join (hash!0))
processBlock : [1024] -> [8][64] -> [8][64]
processBlock block Hprev = Hs
where
Mi = split block : [16][64]
Ws = (messageSch Mi)
round = [Hprev] # [ (step r (Ws@t) t) | t <- [0..79] | r <- round ]
Hs = [ (x + H) | x <- (round!0) | H <- Hprev ]
step : [8][64] -> [64] -> [8] -> [8][64]
step [a, b, c, d, e, f, g, h] Wt t = [a', b', c', d', e', f', g', h']
where
T1 = h + (SIGMA1 e) + (Ch e f g) + (K@t) + Wt
T2 = (SIGMA0 a) + (Maj a b c)
h' = g
g' = f
f' = e
e' = d + T1
d' = c
c' = b
b' = a
a' = T1 + T2
messageSch : [16][64] -> [80][64]
messageSch Mi = W
where
W = Mi # [ (sigma1 (W@(t-2))) + (W@(t-7)) + (sigma0 (W@(t-15))) + (W@(t-16)) | t <- [16..79] ]
pad : {l, k} (fin l,
l <= ((2^^128) - 1),
l >= 0,
fin k,
k - l >= 129,
k == 128 + l + 1 + 1024 - ((l+129)%1024),
k%1024 == 0) => [l] -> [k]
pad M = M # (1:[1]) # (0:[k-128-l-1]) # (`l:[128])
Ch : [64] -> [64] -> [64] -> [64]
Ch x y z = (x && y) ^ ((~x) && z)
Maj : [64] -> [64] -> [64] -> [64]
Maj x y z = (x && y) ^ (x && z) ^ (y && z)
SIGMA0 : [64] -> [64]
SIGMA0 x = (x >>> 28) ^ (x >>> 34) ^ (x >>> 39)
SIGMA1 : [64] -> [64]
SIGMA1 x = (x >>> 14) ^ (x >>> 18) ^ (x >>> 41)
sigma0 : [64] -> [64]
sigma0 x = (x >>> 1) ^ (x >>> 8) ^ (x >> 7)
sigma1 : [64] -> [64]
sigma1 x = (x >>> 19) ^ (x >>> 61) ^ (x >> 6)
H0 = [ 0x6a09e667f3bcc908, 0xbb67ae8584caa73b, 0x3c6ef372fe94f82b, 0xa54ff53a5f1d36f1,
0x510e527fade682d1, 0x9b05688c2b3e6c1f, 0x1f83d9abfb41bd6b, 0x5be0cd19137e2179 ]
K = [
0x428a2f98d728ae22, 0x7137449123ef65cd, 0xb5c0fbcfec4d3b2f, 0xe9b5dba58189dbbc,
0x3956c25bf348b538, 0x59f111f1b605d019, 0x923f82a4af194f9b, 0xab1c5ed5da6d8118,
0xd807aa98a3030242, 0x12835b0145706fbe, 0x243185be4ee4b28c, 0x550c7dc3d5ffb4e2,
0x72be5d74f27b896f, 0x80deb1fe3b1696b1, 0x9bdc06a725c71235, 0xc19bf174cf692694,
0xe49b69c19ef14ad2, 0xefbe4786384f25e3, 0x0fc19dc68b8cd5b5, 0x240ca1cc77ac9c65,
0x2de92c6f592b0275, 0x4a7484aa6ea6e483, 0x5cb0a9dcbd41fbd4, 0x76f988da831153b5,
0x983e5152ee66dfab, 0xa831c66d2db43210, 0xb00327c898fb213f, 0xbf597fc7beef0ee4,
0xc6e00bf33da88fc2, 0xd5a79147930aa725, 0x06ca6351e003826f, 0x142929670a0e6e70,
0x27b70a8546d22ffc, 0x2e1b21385c26c926, 0x4d2c6dfc5ac42aed, 0x53380d139d95b3df,
0x650a73548baf63de, 0x766a0abb3c77b2a8, 0x81c2c92e47edaee6, 0x92722c851482353b,
0xa2bfe8a14cf10364, 0xa81a664bbc423001, 0xc24b8b70d0f89791, 0xc76c51a30654be30,
0xd192e819d6ef5218, 0xd69906245565a910, 0xf40e35855771202a, 0x106aa07032bbd1b8,
0x19a4c116b8d2d0c8, 0x1e376c085141ab53, 0x2748774cdf8eeb99, 0x34b0bcb5e19b48a8,
0x391c0cb3c5c95a63, 0x4ed8aa4ae3418acb, 0x5b9cca4f7763e373, 0x682e6ff3d6b2b8a3,
0x748f82ee5defb2fc, 0x78a5636f43172f60, 0x84c87814a1f0ab72, 0x8cc702081a6439ec,
0x90befffa23631e28, 0xa4506cebde82bde9, 0xbef9a3f7b2c67915, 0xc67178f2e372532b,
0xca273eceea26619c, 0xd186b8c721c0c207, 0xeada7dd6cde0eb1e, 0xf57d4f7fee6ed178,
0x06f067aa72176fba, 0x0a637dc5a2c898a6, 0x113f9804bef90dae, 0x1b710b35131c471b,
0x28db77f523047d84, 0x32caab7b40c72493, 0x3c9ebe0a15c9bebc, 0x431d67c49c100d4c,
0x4cc5d4becb3e42b6, 0x597f299cfc657e2a, 0x5fcb6fab3ad6faec, 0x6c44198c4a475817
]
property testVector1 x = sha512 0xfd2203e467574e834ab07c9097ae164532f24be1eb5d88f1af7748ceff0d2c67a21f4e4097f9d3bb4e9fbf97186e0db6db0100230a52b453d421f8ab9c9a6043aa3295ea20d2f06a2f37470d8a99075f1b8a8336f6228cf08b5942fc1fb4299c7d2480e8e82bce175540bdfad7752bc95b577f229515394f3ae5cec870a4b2f8 == 0xa21b1077d52b27ac545af63b32746c6e3c51cb0cb9f281eb9f3580a6d4996d5c9917d2a6e484627a9d5a06fa1b25327a9d710e027387fc3e07d7c4d14c6086cc cryptol-2.4.0/bench/data/ZUC.cry 0000644 0000000 0000000 00000026663 12737220176 014573 0 ustar 00 0000000 0000000 // Copyright (c) 2011-2016 Galois, Inc.
// An implementation of ZUC, Version 1.5
// Version info: If the following variable is set to True, then we implement
// Version 1.5 of ZUC. Otherwise, version 1.4 is implemented. There are
// precisely two points in the implementation where the difference matters,
// search for occurrences of version1_5 to spot them.
// Note that the ZUC test vectors below will not work for version 1.4, as the
// old test vectors are no longer published.
version1_5 : Bit
version1_5 = False
// addition in GF(2^31-1) over a list of terms
add : {a} (fin a) => [a][31] -> [31]
add xs =
sums ! 0
where
sums =
[0] #
[plus (s, x) | s <- sums
| x <- xs]
// the binary addition specified in the note at the end of section 3.2
plus : ([31], [31]) -> [31]
plus (a, b) =
if sab @ 0 then sab' + 1 else sab'
where
sab : [32]
sab = ((zero : [1]) # a) + ((zero : [1]) # b)
sab' : [31]
sab' = drop sab
// The ZUC LFSR is 16 31-bit words
type LFSR = [16][31]
// Section 3.2
LFSRWithInitializationMode : ([31], LFSR) -> LFSR
LFSRWithInitializationMode (u, ss) =
ss @@ [1 .. 15] # [s16]
where
v = add [s <<< c | s <- ss @@ [15, 13, 10, 4, 0, 0]
| c <- [15, 17, 21, 20, 8, 0]]
vu = if version1_5 then add [v, u] else v ^ u
s16 = if vu == 0 then `0x7FFFFFFF else vu
// Section 3.2
LFSRWithWorkMode : LFSR -> LFSR
LFSRWithWorkMode ss =
ss @@ [1 .. 15] # [s16]
where
v = add [s <<< c | s <- ss @@ [15, 13, 10, 4, 0, 0]
| c <- [15, 17, 21, 20, 8, 0]]
s16 = if v == 0 then `0x7FFFFFFF else v
// Section 3.3
BitReorganization : LFSR -> [4][32]
BitReorganization ss =
[ hi s15 # lo s14
, lo s11 # hi s9
, lo s7 # hi s5
, lo s2 # hi s0]
where
lo : [31] -> [16]
hi : [31] -> [16]
lo x = x @@ [15 .. 30]
hi x = x @@ [0 .. 15]
[s0, s2, s5, s7, s9, s11, s14, s15] = ss @@ [0, 2, 5, 7, 9, 11, 14, 15]
// Section 3.4
F : ([3][32], [2][32]) -> ([32], [2][32])
F ([X0, X1, X2], [R1, R2]) =
(W, [R1', R2'])
where
W = (X0 ^ R1) + R2
W1 = R1 + X1
W2 = R2 ^ X2
[W1H, W1L] = split W1
[W2H, W2L] = split W2
R1' = S (L1 (W1L # W2H))
R2' = S (L2 (W2L # W1H))
// Section 3.4.1
S : [32] -> [32]
S X =
Y0 # Y1 # Y2 # Y3
where
[X0, X1, X2, X3] = split X
[Y0, Y1, Y2, Y3] = [S0 X0, S1 X1, S2 X2, S3 X3]
// Example 8
property example8 = S(0x12345678) == 0xF9C05A4E
S0 : [8] -> [8]
S1 : [8] -> [8]
S2 : [8] -> [8]
S3 : [8] -> [8]
S0 x = S0Table @ x
S1 x = S1Table @ x
S2 = S0
S3 = S1
// Table 3.1
S0Table : [256][8]
S0Table =
[0x3E, 0x72, 0x5B, 0x47, 0xCA, 0xE0, 0x00, 0x33, 0x04, 0xD1, 0x54,
0x98, 0x09, 0xB9, 0x6D, 0xCB, 0x7B, 0x1B, 0xF9, 0x32, 0xAF, 0x9D,
0x6A, 0xA5, 0xB8, 0x2D, 0xFC, 0x1D, 0x08, 0x53, 0x03, 0x90, 0x4D,
0x4E, 0x84, 0x99, 0xE4, 0xCE, 0xD9, 0x91, 0xDD, 0xB6, 0x85, 0x48,
0x8B, 0x29, 0x6E, 0xAC, 0xCD, 0xC1, 0xF8, 0x1E, 0x73, 0x43, 0x69,
0xC6, 0xB5, 0xBD, 0xFD, 0x39, 0x63, 0x20, 0xD4, 0x38, 0x76, 0x7D,
0xB2, 0xA7, 0xCF, 0xED, 0x57, 0xC5, 0xF3, 0x2C, 0xBB, 0x14, 0x21,
0x06, 0x55, 0x9B, 0xE3, 0xEF, 0x5E, 0x31, 0x4F, 0x7F, 0x5A, 0xA4,
0x0D, 0x82, 0x51, 0x49, 0x5F, 0xBA, 0x58, 0x1C, 0x4A, 0x16, 0xD5,
0x17, 0xA8, 0x92, 0x24, 0x1F, 0x8C, 0xFF, 0xD8, 0xAE, 0x2E, 0x01,
0xD3, 0xAD, 0x3B, 0x4B, 0xDA, 0x46, 0xEB, 0xC9, 0xDE, 0x9A, 0x8F,
0x87, 0xD7, 0x3A, 0x80, 0x6F, 0x2F, 0xC8, 0xB1, 0xB4, 0x37, 0xF7,
0x0A, 0x22, 0x13, 0x28, 0x7C, 0xCC, 0x3C, 0x89, 0xC7, 0xC3, 0x96,
0x56, 0x07, 0xBF, 0x7E, 0xF0, 0x0B, 0x2B, 0x97, 0x52, 0x35, 0x41,
0x79, 0x61, 0xA6, 0x4C, 0x10, 0xFE, 0xBC, 0x26, 0x95, 0x88, 0x8A,
0xB0, 0xA3, 0xFB, 0xC0, 0x18, 0x94, 0xF2, 0xE1, 0xE5, 0xE9, 0x5D,
0xD0, 0xDC, 0x11, 0x66, 0x64, 0x5C, 0xEC, 0x59, 0x42, 0x75, 0x12,
0xF5, 0x74, 0x9C, 0xAA, 0x23, 0x0E, 0x86, 0xAB, 0xBE, 0x2A, 0x02,
0xE7, 0x67, 0xE6, 0x44, 0xA2, 0x6C, 0xC2, 0x93, 0x9F, 0xF1, 0xF6,
0xFA, 0x36, 0xD2, 0x50, 0x68, 0x9E, 0x62, 0x71, 0x15, 0x3D, 0xD6,
0x40, 0xC4, 0xE2, 0x0F, 0x8E, 0x83, 0x77, 0x6B, 0x25, 0x05, 0x3F,
0x0C, 0x30, 0xEA, 0x70, 0xB7, 0xA1, 0xE8, 0xA9, 0x65, 0x8D, 0x27,
0x1A, 0xDB, 0x81, 0xB3, 0xA0, 0xF4, 0x45, 0x7A, 0x19, 0xDF, 0xEE,
0x78, 0x34, 0x60]
// Table 3.2
S1Table : [256][8]
S1Table =
[0x55, 0xC2, 0x63, 0x71, 0x3B, 0xC8, 0x47, 0x86, 0x9F, 0x3C, 0xDA,
0x5B, 0x29, 0xAA, 0xFD, 0x77, 0x8C, 0xC5, 0x94, 0x0C, 0xA6, 0x1A,
0x13, 0x00, 0xE3, 0xA8, 0x16, 0x72, 0x40, 0xF9, 0xF8, 0x42, 0x44,
0x26, 0x68, 0x96, 0x81, 0xD9, 0x45, 0x3E, 0x10, 0x76, 0xC6, 0xA7,
0x8B, 0x39, 0x43, 0xE1, 0x3A, 0xB5, 0x56, 0x2A, 0xC0, 0x6D, 0xB3,
0x05, 0x22, 0x66, 0xBF, 0xDC, 0x0B, 0xFA, 0x62, 0x48, 0xDD, 0x20,
0x11, 0x06, 0x36, 0xC9, 0xC1, 0xCF, 0xF6, 0x27, 0x52, 0xBB, 0x69,
0xF5, 0xD4, 0x87, 0x7F, 0x84, 0x4C, 0xD2, 0x9C, 0x57, 0xA4, 0xBC,
0x4F, 0x9A, 0xDF, 0xFE, 0xD6, 0x8D, 0x7A, 0xEB, 0x2B, 0x53, 0xD8,
0x5C, 0xA1, 0x14, 0x17, 0xFB, 0x23, 0xD5, 0x7D, 0x30, 0x67, 0x73,
0x08, 0x09, 0xEE, 0xB7, 0x70, 0x3F, 0x61, 0xB2, 0x19, 0x8E, 0x4E,
0xE5, 0x4B, 0x93, 0x8F, 0x5D, 0xDB, 0xA9, 0xAD, 0xF1, 0xAE, 0x2E,
0xCB, 0x0D, 0xFC, 0xF4, 0x2D, 0x46, 0x6E, 0x1D, 0x97, 0xE8, 0xD1,
0xE9, 0x4D, 0x37, 0xA5, 0x75, 0x5E, 0x83, 0x9E, 0xAB, 0x82, 0x9D,
0xB9, 0x1C, 0xE0, 0xCD, 0x49, 0x89, 0x01, 0xB6, 0xBD, 0x58, 0x24,
0xA2, 0x5F, 0x38, 0x78, 0x99, 0x15, 0x90, 0x50, 0xB8, 0x95, 0xE4,
0xD0, 0x91, 0xC7, 0xCE, 0xED, 0x0F, 0xB4, 0x6F, 0xA0, 0xCC, 0xF0,
0x02, 0x4A, 0x79, 0xC3, 0xDE, 0xA3, 0xEF, 0xEA, 0x51, 0xE6, 0x6B,
0x18, 0xEC, 0x1B, 0x2C, 0x80, 0xF7, 0x74, 0xE7, 0xFF, 0x21, 0x5A,
0x6A, 0x54, 0x1E, 0x41, 0x31, 0x92, 0x35, 0xC4, 0x33, 0x07, 0x0A,
0xBA, 0x7E, 0x0E, 0x34, 0x88, 0xB1, 0x98, 0x7C, 0xF3, 0x3D, 0x60,
0x6C, 0x7B, 0xCA, 0xD3, 0x1F, 0x32, 0x65, 0x04, 0x28, 0x64, 0xBE,
0x85, 0x9B, 0x2F, 0x59, 0x8A, 0xD7, 0xB0, 0x25, 0xAC, 0xAF, 0x12,
0x03, 0xE2, 0xF2]
// Section 3.4.2
L1 : [32] -> [32]
L1 X = X ^ X <<< 2 ^ X <<< 10 ^ X <<< 18 ^ X <<< 24
// Section 3.4.2
L2 : [32] -> [32]
L2 X = X ^ X <<< 8 ^ X <<< 14 ^ X <<< 22 ^ X <<< 30
// Section 3.5
LoadKey : ([128], [128]) -> LFSR
LoadKey (key, iv) =
[k # d # i | k <- ks
| i <- is
| d <- ds]
where
ks : [16][8]
ks = split key
is : [16][8]
is = split iv
ds : [16][15]
ds =
[ 0b100010011010111, 0b010011010111100
, 0b110001001101011, 0b001001101011110
, 0b101011110001001, 0b011010111100010
, 0b111000100110101, 0b000100110101111
, 0b100110101111000, 0b010111100010011
, 0b110101111000100, 0b001101011110001
, 0b101111000100110, 0b011110001001101
, 0b111100010011010, 0b100011110101100
]
type ZUC = (LFSR, [32], [32])
// Return an infinite sequence of ZUC states by applying the initialization step
// repeatedly. This is a generalization of section 3.6.1
InitializeZUC : ([128], [128]) -> [inf]ZUC
InitializeZUC (key, iv) =
outs
where
initLFSR = LoadKey (key, iv)
outs = [(initLFSR, 0, 0)] # [step out | out <- outs]
step (lfsr, R1, R2) =
(LFSRWithInitializationMode (drop (w >> 1), lfsr), R1', R2')
where
[X0, X1, X2, X3] = BitReorganization lfsr
(w', [R1', R2']) = F ([X0, X1, X2], [R1, R2])
w = if version1_5 then w' else w' ^ X3
// Section 3.6.2
WorkingStage : ZUC -> ZUC
WorkingStage (lfsr, R1, R2) =
(lfsr', R1', R2')
where
[X0, X1, X2, _] = BitReorganization lfsr
(_, [R1', R2']) = F ([X0, X1, X2], [R1, R2])
lfsr' = LFSRWithWorkMode lfsr
// Section 3.6.2
ProductionStage : ZUC -> ([32], ZUC)
ProductionStage (lfsr, R1, R2) =
(w ^ X3, (lfsr', R1', R2'))
where
[X0, X1, X2, X3] = BitReorganization lfsr
(w, [R1', R2']) = F ([X0, X1, X2], [R1, R2])
lfsr' = LFSRWithWorkMode lfsr
// ZUC API
ZUC : [128] -> [128] -> [inf][32]
ZUC key iv =
tail [w | (w, _) <- zucs]
where
initZuc = WorkingStage (InitializeZUC (key, iv) @ 32)
zucs = [(zero, initZuc)] # [ProductionStage zuc | (_, zuc) <- zucs]
// Test vectors
property ZUC_TestVectors =
t1 && t2 && t3 && t4
where
t1 = take (ZUC zero zero ) == [0x27BEDE74, 0x018082DA]
t2 = take (ZUC (~zero) (~zero)) == [0x0657CFA0, 0x7096398B]
t3 = take (ZUC (join [ 0x3D, 0x4C, 0x4B, 0xE9, 0x6A, 0x82, 0xFD, 0xAE
, 0xB5, 0x8F, 0x64, 0x1D, 0xB1, 0x7B, 0x45, 0x5B
])
(join [ 0x84, 0x31, 0x9A, 0xA8, 0xDE, 0x69, 0x15, 0xCA
, 0x1F, 0x6B, 0xDA, 0x6B, 0xFB, 0xD8, 0xC7, 0x66
])) == [0x14F1C272, 0x3279C419]
t4 = take ks # [ks @ 1999] == [0xED4400E7, 0x0633E5C5, 0x7A574CDB]
where
ks = ZUC (join [ 0x4D, 0x32, 0x0B, 0xFA, 0xD4, 0xC2, 0x85, 0xBF
, 0xD6, 0xB8, 0xBD, 0x00, 0xF3, 0x9D, 0x8B, 0x41
])
(join [ 0x52, 0x95, 0x9D, 0xAB, 0xA0, 0xBF, 0x17, 0x6E
, 0xCE, 0x2D, 0xC3, 0x15, 0x04, 0x9E, 0xB5, 0x74
])
// 3.3-3.6 of the implementor's test data document lists "LFSR-state at the
// beginning", which is immediately after running LoadKey.
property LoadKey_TestVectors =
[ LoadKey(k, iv) == lfsr0
| k <- ks
| iv <- ivs
| lfsr0 <- lfsr0s
] == ~0
where
ks = [ 0
, ~0
, 0x3d4c4be96a82fdaeb58f641db17b455b
, 0x4d320bfad4c285bfd6b8bd00f39d8b41
]
ivs = [ 0
, ~0
, 0x84319aa8de6915ca1f6bda6bfbd8c766
, 0x52959daba0bf176ece2dc315049eb574
]
lfsr0s = [ [ `0x0044d700, `0x0026bc00, `0x00626b00, `0x00135e00
, `0x00578900, `0x0035e200, `0x00713500, `0x0009af00
, `0x004d7800, `0x002f1300, `0x006bc400, `0x001af100
, `0x005e2600, `0x003c4d00, `0x00789a00, `0x0047ac00
]
, [ `0x7fc4d7ff, `0x7fa6bcff, `0x7fe26bff, `0x7f935eff
, `0x7fd789ff, `0x7fb5e2ff, `0x7ff135ff, `0x7f89afff
, `0x7fcd78ff, `0x7faf13ff, `0x7febc4ff, `0x7f9af1ff
, `0x7fde26ff, `0x7fbc4dff, `0x7ff89aff, `0x7fc7acff
]
, [ `0x1ec4d784, `0x2626bc31, `0x25e26b9a, `0x74935ea8
, `0x355789de, `0x4135e269, `0x7ef13515, `0x5709afca
, `0x5acd781f, `0x47af136b, `0x326bc4da, `0x0e9af16b
, `0x58de26fb, `0x3dbc4dd8, `0x22f89ac7, `0x2dc7ac66
]
, [ `0x26c4d752, `0x1926bc95, `0x05e26b9d, `0x7d135eab
, `0x6a5789a0, `0x6135e2bf, `0x42f13517, `0x5f89af6e
, `0x6b4d78ce, `0x5c2f132d, `0x5eebc4c3, `0x001af115
, `0x79de2604, `0x4ebc4d9e, `0x45f89ab5, `0x20c7ac74
]
]
// Collision attack on ZUC. Only version1.5 is resistant to it. Thus, the
// following theorem holds only when version1_5 is set to True.
//
// NB. We only compare the first output of the InitializeZUC sequence, as it
// cuts down on the problem size and is sufficient to ensure the iv's will be
// the same. That is, if this theorem fails, then so would the final iv's used
// by ZUC.
//
// Use a solver other than CVC4; Z3 and Boolector do it quickly.
property ZUC_isResistantToCollisionAttack k iv1 iv2 =
if iv1 != iv2
then InitializeZUC (k, iv1) @ 1 != InitializeZUC (k, iv2) @ 1
else True
cryptol-2.4.0/cryptol/ 0000755 0000000 0000000 00000000000 12737220176 013102 5 ustar 00 0000000 0000000 cryptol-2.4.0/cryptol/Main.hs 0000644 0000000 0000000 00000017501 12737220176 014326 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import OptParser
import Cryptol.REPL.Command (loadCmd,loadPrelude)
import Cryptol.REPL.Monad (REPL,updateREPLTitle,setUpdateREPLTitle,
io,prependSearchPath,setSearchPath)
import qualified Cryptol.REPL.Monad as REPL
import REPL.Haskeline
import REPL.Logo
import Cryptol.Utils.PP
import Cryptol.Version (commitHash, commitBranch, commitDirty)
import Paths_cryptol (version)
import Control.Monad (when)
import Data.Maybe (isJust)
import Data.Version (showVersion)
import GHC.IO.Encoding (setLocaleEncoding, utf8)
import System.Console.GetOpt
(OptDescr(..),ArgOrder(..),ArgDescr(..),getOpt,usageInfo)
import System.Directory (getTemporaryDirectory, removeFile)
import System.Environment (getArgs, getProgName, lookupEnv)
import System.Exit (exitFailure)
import System.FilePath (searchPathSeparator, splitSearchPath, takeDirectory)
import System.IO (hClose, hPutStr, openTempFile)
import Prelude ()
import Prelude.Compat
data Options = Options
{ optLoad :: [FilePath]
, optVersion :: Bool
, optHelp :: Bool
, optBatch :: Maybe FilePath
, optCommands :: [String]
, optCryptolrc :: Cryptolrc
, optCryptolPathOnly :: Bool
} deriving (Show)
defaultOptions :: Options
defaultOptions = Options
{ optLoad = []
, optVersion = False
, optHelp = False
, optBatch = Nothing
, optCommands = []
, optCryptolrc = CryrcDefault
, optCryptolPathOnly = False
}
options :: [OptDescr (OptParser Options)]
options =
[ Option "b" ["batch"] (ReqArg setBatchScript "FILE")
"run the script provided and exit"
, Option "c" ["command"] (ReqArg addCommand "COMMAND")
(concat [ "run the given command and then exit; if multiple --command "
, "arguments are given, run them in the order they appear "
, "on the command line (overrides --batch)"
])
, Option "v" ["version"] (NoArg setVersion)
"display version number"
, Option "h" ["help"] (NoArg setHelp)
"display this message"
, Option "" ["ignore-cryptolrc"] (NoArg setCryrcDisabled)
"disable reading of .cryptolrc files"
, Option "" ["cryptolrc-script"] (ReqArg addCryrc "FILE")
"read additional .cryptolrc files"
, Option "" ["cryptolpath-only"] (NoArg setCryptolPathOnly)
"only look for .cry files in CRYPTOLPATH; don't use built-in locations"
]
-- | Set a single file to be loaded. This should be extended in the future, if
-- we ever plan to allow multiple files to be loaded at the same time.
addFile :: String -> OptParser Options
addFile path = modify $ \ opts -> opts { optLoad = [ path ] }
-- | Add a command to be run on interpreter startup.
addCommand :: String -> OptParser Options
addCommand cmd =
modify $ \ opts -> opts { optCommands = cmd : optCommands opts }
-- | Set a batch script to be run.
setBatchScript :: String -> OptParser Options
setBatchScript path = modify $ \ opts -> opts { optBatch = Just path }
-- | Signal that version should be displayed.
setVersion :: OptParser Options
setVersion = modify $ \ opts -> opts { optVersion = True }
-- | Signal that help should be displayed.
setHelp :: OptParser Options
setHelp = modify $ \ opts -> opts { optHelp = True }
-- | Disable .cryptolrc files entirely
setCryrcDisabled :: OptParser Options
setCryrcDisabled = modify $ \ opts -> opts { optCryptolrc = CryrcDisabled }
-- | Add another file to read as a @.cryptolrc@ file, unless @.cryptolrc@
-- files have been disabled
addCryrc :: String -> OptParser Options
addCryrc path = modify $ \ opts ->
case optCryptolrc opts of
CryrcDefault -> opts { optCryptolrc = CryrcFiles [path] }
CryrcDisabled -> opts
CryrcFiles xs -> opts { optCryptolrc = CryrcFiles (path:xs) }
setCryptolPathOnly :: OptParser Options
setCryptolPathOnly = modify $ \opts -> opts { optCryptolPathOnly = True }
-- | Parse arguments.
parseArgs :: [String] -> Either [String] Options
parseArgs args = case getOpt (ReturnInOrder addFile) options args of
(ps,[],[]) -> runOptParser defaultOptions (mconcat ps)
(_,_,errs) -> Left errs
displayVersion :: IO ()
displayVersion = do
let ver = showVersion version
putStrLn ("Cryptol " ++ ver)
putStrLn ("Git commit " ++ commitHash)
putStrLn (" branch " ++ commitBranch ++ dirtyLab)
where
dirtyLab | commitDirty = " (non-committed files present during build)"
| otherwise = ""
displayHelp :: [String] -> IO ()
displayHelp errs = do
prog <- getProgName
let banner = "Usage: " ++ prog ++ " [OPTIONS]"
paraLines = fsep . map text . words . unlines
ppEnv (varname, desc) = hang varname 4 (paraLines $ desc)
envs = [
( "CRYPTOLPATH"
, [ "A `" ++ [searchPathSeparator] ++ "`-separated"
, "list of directories to be searched for Cryptol modules in"
, "addition to the default locations"
]
)
, ( "SBV_{ABC,BOOLECTOR,CVC4,MATHSAT,YICES,Z3}_OPTIONS"
, [ "A string of command-line arguments to be passed to the"
, "corresponding solver invoked for `:sat` and `:prove`"
]
)
]
putStrLn (usageInfo (concat (errs ++ [banner])) options)
print $ hang "Influential environment variables:"
4 (vcat (map ppEnv envs))
main :: IO ()
main = do
setLocaleEncoding utf8
args <- getArgs
case parseArgs args of
Left errs -> do
displayHelp errs
exitFailure
Right opts
| optHelp opts -> displayHelp []
| optVersion opts -> displayVersion
| otherwise -> do
(opts', mCleanup) <- setupCmdScript opts
repl (optCryptolrc opts')
(optBatch opts')
(setupREPL opts')
case mCleanup of
Nothing -> return ()
Just cmdFile -> removeFile cmdFile
setupCmdScript :: Options -> IO (Options, Maybe FilePath)
setupCmdScript opts =
case optCommands opts of
[] -> return (opts, Nothing)
cmds -> do
tmpdir <- getTemporaryDirectory
(path, h) <- openTempFile tmpdir "cmds.icry"
hPutStr h (unlines cmds)
hClose h
when (isJust (optBatch opts)) $
putStrLn "[warning] --command argument specified; ignoring batch file"
return (opts { optBatch = Just path }, Just path)
setupREPL :: Options -> REPL ()
setupREPL opts = do
smoke <- REPL.smokeTest
case smoke of
[] -> return ()
_ -> io $ do
print (hang "Errors encountered on startup; exiting:"
4 (vcat (map pp smoke)))
exitFailure
displayLogo True
setUpdateREPLTitle setREPLTitle
updateREPLTitle
mCryptolPath <- io $ lookupEnv "CRYPTOLPATH"
case mCryptolPath of
Nothing -> return ()
Just path | optCryptolPathOnly opts -> setSearchPath path'
| otherwise -> prependSearchPath path'
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
-- Windows paths search from end to beginning
where path' = reverse (splitSearchPath path)
#else
where path' = splitSearchPath path
#endif
case optBatch opts of
Nothing -> return ()
-- add the directory containing the batch file to the module search path
Just file -> prependSearchPath [ takeDirectory file ]
case optLoad opts of
[] -> loadPrelude `REPL.catch` \x -> io $ print $ pp x
[l] -> loadCmd l `REPL.catch` \x -> do
io $ print $ pp x
-- If the requested file fails to load, load the prelude instead
loadPrelude `REPL.catch` \y -> do
io $ print $ pp y
_ -> io $ putStrLn "Only one file may be loaded at the command line."
cryptol-2.4.0/cryptol/OptParser.hs 0000644 0000000 0000000 00000001723 12737220176 015360 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module OptParser where
import Data.Monoid (Endo(..))
import Prelude ()
import Prelude.Compat
data OptParser opt
= OptSuccess (Endo opt)
| OptFailure [String]
instance Monoid (OptParser opt) where
mempty = OptSuccess mempty
l `mappend` r = case (l,r) of
(OptSuccess f,OptSuccess g) -> OptSuccess (f `mappend` g)
(OptFailure a,OptFailure b) -> OptFailure (a `mappend` b)
(OptFailure _,_) -> l
(_,OptFailure _) -> r
runOptParser :: opt -> OptParser opt -> Either [String] opt
runOptParser def parse = case parse of
OptSuccess update -> Right (appEndo update def)
OptFailure msgs -> Left msgs
modify :: (opt -> opt) -> OptParser opt
modify f = OptSuccess (Endo f)
report :: String -> OptParser opt
report msg = OptFailure [msg]
cryptol-2.4.0/cryptol/REPL/ 0000755 0000000 0000000 00000000000 12737220176 013644 5 ustar 00 0000000 0000000 cryptol-2.4.0/cryptol/REPL/Haskeline.hs 0000644 0000000 0000000 00000020623 12737220176 016106 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternGuards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module REPL.Haskeline where
import Cryptol.REPL.Command
import Cryptol.REPL.Monad
import Cryptol.REPL.Trie
import Cryptol.Utils.PP
import qualified Control.Exception as X
import Control.Monad (guard, join, when)
import qualified Control.Monad.Trans.Class as MTL
import Control.Monad.Trans.Control
import Data.Char (isAlphaNum, isSpace)
import Data.Function (on)
import Data.List (isPrefixOf,nub,sortBy,sort)
import System.Console.ANSI (setTitle)
import System.Console.Haskeline
import System.Directory ( doesFileExist
, getHomeDirectory
, getCurrentDirectory)
import System.FilePath ((>))
import Prelude ()
import Prelude.Compat
-- | Haskeline-specific repl implementation.
repl :: Cryptolrc -> Maybe FilePath -> REPL () -> IO ()
repl cryrc mbBatch begin =
do settings <- setHistoryFile (replSettings isBatch)
runREPL isBatch (runInputTBehavior behavior settings body)
where
body = withInterrupt $ do
MTL.lift evalCryptolrc
MTL.lift begin
loop
(isBatch,behavior) = case mbBatch of
Nothing -> (False,defaultBehavior)
Just path -> (True,useFile path)
loop = do
prompt <- MTL.lift getPrompt
mb <- handleInterrupt (return (Just "")) (getInputLines prompt [])
case mb of
Just line
| Just cmd <- parseCommand findCommandExact line -> do
continue <- MTL.lift $ do
handleInterrupt handleCtrlC (runCommand cmd)
shouldContinue
when continue loop
| otherwise -> loop
Nothing -> return ()
getInputLines prompt ls =
do mb <- getInputLine prompt
let newPropmpt = map (\_ -> ' ') prompt
case mb of
Nothing -> return Nothing
Just l | not (null l) && last l == '\\' ->
getInputLines newPropmpt (init l : ls)
| otherwise -> return $ Just $ unlines $ reverse $ l : ls
evalCryptolrc =
case cryrc of
CryrcDefault -> do
here <- io $ getCurrentDirectory
home <- io $ getHomeDirectory
let dcHere = here > ".cryptolrc"
dcHome = home > ".cryptolrc"
isHere <- io $ doesFileExist dcHere
isHome <- io $ doesFileExist dcHome
if | isHere -> slurp dcHere
| isHome -> slurp dcHome
| otherwise -> whenDebug $ io $ putStrLn "no .cryptolrc found"
CryrcFiles paths -> mapM_ slurp paths
CryrcDisabled -> return ()
-- | Actually read the contents of a file, but don't save the
-- history
--
-- XXX: friendlier error message would be nice if the file can't be
-- found, but since these will be specified on the command line it
-- should be obvious what's going wrong
slurp path = do
let settings' = defaultSettings { autoAddHistory = False }
runInputTBehavior (useFile path) settings' (withInterrupt loop)
-- | Try to set the history file.
setHistoryFile :: Settings REPL -> IO (Settings REPL)
setHistoryFile ss =
do dir <- getHomeDirectory
return ss { historyFile = Just (dir > ".cryptol_history") }
`X.catch` \(SomeException {}) -> return ss
-- | Haskeline settings for the REPL.
replSettings :: Bool -> Settings REPL
replSettings isBatch = Settings
{ complete = cryptolCommand
, historyFile = Nothing
, autoAddHistory = not isBatch
}
-- .cryptolrc ------------------------------------------------------------------
-- | Configuration of @.cryptolrc@ file behavior. The default option
-- searches the following locations in order, and evaluates the first
-- file that exists in batch mode on interpreter startup:
--
-- 1. $PWD/.cryptolrc
-- 2. $HOME/.cryptolrc
--
-- If files are specified, they will all be evaluated, but none of the
-- default files will be (unless they are explicitly specified).
--
-- The disabled option inhibits any reading of any .cryptolrc files.
data Cryptolrc =
CryrcDefault
| CryrcDisabled
| CryrcFiles [FilePath]
deriving (Show)
-- Utilities -------------------------------------------------------------------
instance MonadException REPL where
controlIO f = join $ liftBaseWith $ \f' ->
f $ RunIO $ \m -> restoreM <$> (f' m)
-- Titles ----------------------------------------------------------------------
mkTitle :: Maybe LoadedModule -> String
mkTitle lm = maybe "" (\ m -> pretty m ++ " - ") (lName =<< lm)
++ "cryptol"
setREPLTitle :: REPL ()
setREPLTitle = do
lm <- getLoadedMod
io (setTitle (mkTitle lm))
-- Completion ------------------------------------------------------------------
-- | Completion for cryptol commands.
cryptolCommand :: CompletionFunc REPL
cryptolCommand cursor@(l,r)
| ":" `isPrefixOf` l'
, Just (cmd,rest) <- splitCommand l' = case nub (findCommand cmd) of
[c] | null rest && not (any isSpace l') -> do
return (l, cmdComp cmd c)
| otherwise -> do
(rest',cs) <- cmdArgument (cBody c) (reverse (sanitize rest),r)
return (unwords [rest', reverse cmd],cs)
cmds ->
return (l, concat [ cmdComp l' c | c <- cmds ])
-- Complete all : commands when the line is just a :
| ":" == l' = return (l, concat [ cmdComp l' c | c <- nub (findCommand ":") ])
| otherwise = completeExpr cursor
where
l' = sanitize (reverse l)
-- | Generate completions from a REPL command definition.
cmdComp :: String -> CommandDescr -> [Completion]
cmdComp prefix c = do
cName <- cNames c
guard (prefix `isPrefixOf` cName)
return $ Completion
{ replacement = drop (length prefix) cName
, display = cName
, isFinished = True
}
-- | Dispatch to a completion function based on the kind of completion the
-- command is expecting.
cmdArgument :: CommandBody -> CompletionFunc REPL
cmdArgument ct cursor@(l,_) = case ct of
ExprArg _ -> completeExpr cursor
DeclsArg _ -> (completeExpr +++ completeType) cursor
ExprTypeArg _ -> (completeExpr +++ completeType) cursor
FilenameArg _ -> completeFilename cursor
ShellArg _ -> completeFilename cursor
OptionArg _ -> completeOption cursor
NoArg _ -> return (l,[])
FileExprArg _ -> completeExpr cursor
-- | Additional keywords to suggest in the REPL
-- autocompletion list.
keywords :: [String]
keywords =
[ "else"
, "if"
, "let"
, "then"
, "where"
]
-- | Complete a name from the expression environment.
completeExpr :: CompletionFunc REPL
completeExpr (l,_) = do
ns <- (keywords++) <$> getExprNames
let n = reverse (takeIdent l)
vars = sort $ filter (n `isPrefixOf`) ns
return (l,map (nameComp n) vars)
-- | Complete a name from the type synonym environment.
completeType :: CompletionFunc REPL
completeType (l,_) = do
ns <- getTypeNames
let n = reverse (takeIdent l)
vars = filter (n `isPrefixOf`) ns
return (l,map (nameComp n) vars)
-- | Generate a completion from a prefix and a name.
nameComp :: String -> String -> Completion
nameComp prefix c = Completion
{ replacement = drop (length prefix) c
, display = c
, isFinished = True
}
-- | Return longest identifier (possibly a qualified name) that is a
-- prefix of the given string
takeIdent :: String -> String
takeIdent (c : cs) | isIdentChar c = c : takeIdent cs
takeIdent (':' : ':' : cs) = ':' : ':' : takeIdent cs
takeIdent _ = []
isIdentChar :: Char -> Bool
isIdentChar c = isAlphaNum c || c `elem` "_\'"
-- | Join two completion functions together, merging and sorting their results.
(+++) :: CompletionFunc REPL -> CompletionFunc REPL -> CompletionFunc REPL
(as +++ bs) cursor = do
(_,acs) <- as cursor
(_,bcs) <- bs cursor
return (fst cursor, sortBy (compare `on` replacement) (acs ++ bcs))
-- | Complete an option from the options environment.
--
-- XXX this can do better, as it has access to the expected form of the value
completeOption :: CompletionFunc REPL
completeOption cursor@(l,_) = return (fst cursor, map comp opts)
where
n = reverse l
opts = lookupTrie n userOptions
comp opt = Completion
{ replacement = drop (length n) (optName opt)
, display = optName opt
, isFinished = False
}
cryptol-2.4.0/cryptol/REPL/Logo.hs 0000644 0000000 0000000 00000003002 12737220176 015073 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module REPL.Logo where
import Cryptol.REPL.Monad
import Paths_cryptol (version)
import Cryptol.Version (commitShortHash)
import Data.Version (showVersion)
import System.Console.ANSI
type Version = String
type Logo = [String]
logo :: Bool -> Logo
logo useColor =
[ sgr [SetColor Foreground Dull White] ++ l | l <- ws ]
++ [ sgr [SetColor Foreground Vivid Blue ] ++ l | l <- vs ]
++ [ sgr [SetColor Foreground Dull Blue ] ++ l | l <- ds ]
++ [ sgr [Reset] ]
where
sgr | useColor = setSGRCode
| otherwise = const []
hashText | commitShortHash == "UNKNOWN" = ""
| otherwise = " (" ++ commitShortHash ++ ")"
versionText = "version " ++ showVersion version ++ hashText
ver = sgr [SetColor Foreground Dull White]
++ replicate (lineLen - 20 - length versionText) ' '
++ versionText
ls =
[ " _ _"
, " ___ _ __ _ _ _ __ | |_ ___ | |"
, " / __| \'__| | | | \'_ \\| __/ _ \\| |"
, " | (__| | | |_| | |_) | || (_) | |"
, " \\___|_| \\__, | .__/ \\__\\___/|_|"
, " |___/|_| " ++ ver
]
slen = length ls `div` 3
(ws,rest) = splitAt slen ls
(vs,ds) = splitAt slen rest
lineLen = length (head ls)
displayLogo :: Bool -> REPL ()
displayLogo useColor =unlessBatch (io (mapM_ putStrLn (logo useColor)))
cryptol-2.4.0/cryptol-server/ 0000755 0000000 0000000 00000000000 12737220176 014406 5 ustar 00 0000000 0000000 cryptol-2.4.0/cryptol-server/Main.hs 0000644 0000000 0000000 00000032665 12737220176 015642 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Alpha version of a Cryptol server that communicates via JSON over
-- ZeroMQ. This API is highly unstable and extremely likely to change
-- in the near future.
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wall -fno-warn-type-defaults #-}
module Main where
import Control.Concurrent
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Control
import qualified Control.Exception as X
import Data.Aeson
import Data.Aeson.Encode.Pretty
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import Data.Char
import Data.IORef
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as T
import Data.Word
import Options.Applicative
import System.Environment
import System.Exit
import System.FilePath
import System.Posix.Signals
import System.ZMQ4
import Text.Read
import qualified Cryptol.Eval.Value as E
import Cryptol.REPL.Command
import Cryptol.REPL.Monad
import Cryptol.Symbolic (ProverResult(..))
import qualified Cryptol.Testing.Concrete as Test
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.ModuleSystem as M
import Cryptol.Utils.PP hiding ((<>))
import Cryptol.Aeson ()
import Prelude ()
import Prelude.Compat
data RCommand
= RCEvalExpr Text
| RCApplyFun FunHandle E.Value
| RCTypeOf Text
| RCSetOpt Text Text
| RCCheck Text
| RCExhaust Text
| RCProve Text
| RCSat Text
| RCLoadPrelude
| RCLoadModule FilePath
| RCDecls
| RCUnknownCmd Text
| RCExit
instance FromJSON RCommand where
parseJSON = withObject "RCommand" $ \o -> do
tag <- o .: "tag"
flip (withText "tag") tag $ \case
"evalExpr" -> RCEvalExpr <$> o .: "expr"
"applyFun" -> RCApplyFun <$> o .: "handle" <*> o .: "arg"
"typeOf" -> RCTypeOf <$> o .: "expr"
"setOpt" -> RCSetOpt <$> o .: "key" <*> o .: "value"
"check" -> RCCheck <$> o .: "expr"
"exhaust" -> RCExhaust <$> o .: "expr"
"prove" -> RCProve <$> o .: "expr"
"sat" -> RCSat <$> o .: "expr"
"loadPrelude" -> return RCLoadPrelude
"loadModule" -> RCLoadModule . T.unpack <$> o .: "filePath"
"browse" -> return RCDecls
"exit" -> return RCExit
unknown -> return (RCUnknownCmd unknown)
newtype FunHandle = FH Int
deriving (Eq, Ord, Enum, Bounded, Show)
instance ToJSON FunHandle where
toJSON (FH i) = toJSON i
instance FromJSON FunHandle where
parseJSON v = FH <$> parseJSON v
data RResult
= RRValue E.Value
| RRFunValue FunHandle T.Type
| RRType T.Schema String -- pretty-printed type
| RRDecls M.IfaceDecls
| RRCheck [Test.TestReport]
| RRExhaust [Test.TestReport]
| RRSat [[E.Value]]
-- ^ A list of satisfying assignments. Empty list means unsat, max
-- length determined by @satNum@ interpreter option
| RRProve (Maybe [E.Value])
-- ^ Counterexample if invalid or 'Nothing' if valid
| RRProverError String
| RRInteractiveError REPLException String -- pretty-printed exception
| RRUnknownCmd Text
| RRBadMessage BS.ByteString String
| RROk
| RRInterrupted
instance ToJSON RResult where
toJSON = \case
RRValue v -> object
[ "tag" .= "value", "value" .= v ]
RRFunValue fh t -> object
[ "tag" .= "funValue", "handle" .= fh, "type" .= t ]
RRType s pps -> object
[ "tag" .= "type", "value" .= s, "pp" .= pps ]
RRDecls ifds -> object
[ "tag" .= "decls", "decls" .= ifds ]
RRCheck out -> object
[ "tag" .= "check", "testReport" .= out ]
RRExhaust out -> object
[ "tag" .= "exhaust", "testReport" .= out ]
RRSat out -> object
[ "tag" .= "sat", "assignments" .= out ]
RRProve out -> object
[ "tag" .= "prove", "counterexample" .= out ]
RRProverError msg -> object
[ "tag" .= "proverError", "message" .= msg ]
RRInteractiveError err pps -> object
[ "tag" .= "interactiveError", "error" .= err, "pp" .= pps ]
RRUnknownCmd txt -> object
[ "tag" .= "unknownCommand", "command" .= txt ]
RRBadMessage msg err -> object
[ "tag" .= "badMessage", "message" .= BS.unpack msg, "error" .= err ]
RROk -> object
[ "tag" .= "ok" ]
RRInterrupted -> object
[ "tag" .= "interrupted" ]
data ControlMsg
= CMConnect
-- ^ Request a new Cryptol context and connection
| CMInterrupt Word16
-- ^ Request an interrupt of all current Cryptol contexts
| CMExit
-- ^ Request that the entire server shut down
| CMUnknown Text
-- ^ Unknown message
instance FromJSON ControlMsg where
parseJSON = withObject "ControlMsg" $ \o -> do
tag <- o .: "tag"
flip (withText "tag") tag $ \case
"connect" -> return CMConnect
"interrupt" -> CMInterrupt <$> o .: "port"
"exit" -> return CMExit
other -> return $ CMUnknown other
data ControlReply
= CRConnect Word16
-- ^ Return the port for a new connection
| CRInterrupted
-- ^ Acknowledge receipt of an interrupt command
| CRExiting
-- ^ Acknowledge receipt of an exit command
| CRBadMessage BS.ByteString String
-- ^ Acknowledge receipt of an ill-formed control message
instance ToJSON ControlReply where
toJSON = \case
CRConnect port -> object
[ "tag" .= "connect", "port" .= port ]
CRInterrupted -> object
[ "tag" .= "interrupted" ]
CRExiting -> object
[ "tag" .= "exiting" ]
CRBadMessage msg err -> object
[ "tag" .= "badMessage", "message" .= BS.unpack msg, "error" .= err ]
server :: Word16 -> IO ()
server port =
withContext $ \ctx ->
withSocket ctx Rep $ \rep -> do
let addr = "tcp://127.0.0.1:" ++ show port
putStrLn ("[cryptol-server] coming online at " ++ addr)
bind rep addr
workers <- newIORef Map.empty
let loop = do
msg <- receive rep
putStrLn "[cryptol-server] received message:"
case decodeStrict msg of
Nothing -> BS.putStrLn msg
Just js -> BSL.putStrLn (encodePretty (js :: Value))
case eitherDecodeStrict msg of
Left err -> reply rep $ CRBadMessage msg err
Right CMConnect -> do
putStrLn "[cryptol-server] handling new incoming connection"
newRep <- socket ctx Rep
bind newRep "tcp://127.0.0.1:*"
newAddr <- lastEndpoint newRep
let portStr = reverse . takeWhile isDigit . reverse $ newAddr
workerPort = read portStr
putStrLn ("[cryptol-server] starting worker on interface " ++ newAddr)
tid <- forkFinally (runRepl newRep) (removeWorker workers port)
addNewWorker workers workerPort tid
reply rep $ CRConnect workerPort
Right (CMInterrupt port') -> do
s <- readIORef workers
case Map.lookup port' s of
Nothing -> reply rep $ CRBadMessage msg "invalid worker port"
Just tid -> do
throwTo tid X.UserInterrupt
reply rep $ CRInterrupted
Right CMExit -> do
putStrLn "[cryptol-server] shutting down"
reply rep $ CRExiting
exitSuccess
Right (CMUnknown cmd) -> do
putStrLn ("[cryptol-server] unknown control command: " ++ T.unpack cmd)
reply rep $ CRBadMessage msg "unknown control command"
loop
loop
reply :: (ToJSON a, MonadIO m) => Socket Rep -> a -> m ()
reply rep msg = liftIO $ do
let bmsg = BS.concat . BSL.toChunks . encodePretty $ msg
putStrLn "[cryptol-server] sending response:"
BS.putStrLn bmsg
send rep [] bmsg
addNewWorker :: IORef (Map Word16 ThreadId) -> Word16 -> ThreadId -> IO ()
addNewWorker workers port tid =
atomicModifyIORef workers $ \s -> (Map.insert port tid s, ())
removeWorker :: IORef (Map Word16 ThreadId) -> Word16 -> a -> IO ()
removeWorker workers port _result =
atomicModifyIORef workers $ \s -> (Map.delete port s, ())
runRepl :: Socket Rep -> IO ()
runRepl rep = runREPL False $ do -- TODO: batch mode?
mCryptolPath <- io $ lookupEnv "CRYPTOLPATH"
case mCryptolPath of
Nothing -> return ()
Just path -> prependSearchPath path'
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
-- Windows paths search from end to beginning
where path' = reverse (splitSearchPath path)
#else
where path' = splitSearchPath path
#endif
funHandles <- io $ newIORef (Map.empty, minBound :: FunHandle)
let handle err = reply rep (RRInteractiveError err (show (pp err)))
handleAsync :: X.AsyncException -> IO ()
handleAsync _int = reply rep RRInterrupted
loop = liftBaseWith $ \run -> X.handle handleAsync $ run $ do
msg <- io $ receive rep
io $ putStrLn "[cryptol-worker] received message:"
case decodeStrict msg of
Nothing -> io $ BS.putStrLn msg
Just js -> io $ BSL.putStrLn (encodePretty (js :: Value))
flip catch handle $ case eitherDecodeStrict msg of
Left cmdErr -> reply rep (RRBadMessage msg cmdErr)
Right rc -> case rc of
RCEvalExpr txt -> do
expr <- replParseExpr (T.unpack txt)
(val, ty) <- replEvalExpr expr
case val of
E.VFun f -> do
fh <- io $ atomicModifyIORef' funHandles $ \(m, fh) ->
let m' = Map.insert fh f m
fh' = succ fh
in ((m', fh'), fh)
reply rep (RRFunValue fh ty)
_ -> reply rep (RRValue val)
RCApplyFun fh arg -> do
(m, _) <- io $ readIORef funHandles
case Map.lookup fh m of
Nothing -> reply rep (RRBadMessage "invalid function handle" (show fh))
Just f -> do
case f arg of
E.VFun g -> do
gh <- io $ atomicModifyIORef' funHandles $ \(m', gh) ->
let m'' = Map.insert gh g m'
gh' = succ gh
in ((m'', gh'), gh)
-- TODO: bookkeeping to track the type of this value
reply rep (RRFunValue gh T.tZero)
val -> reply rep (RRValue val)
RCTypeOf txt -> do
expr <- replParseExpr (T.unpack txt)
(_expr, _def, sch) <- replCheckExpr expr
reply rep (RRType sch (show (pp sch)))
RCSetOpt key val -> do
setOptionCmd (T.unpack key ++ "=" ++ T.unpack val)
reply rep RROk
RCCheck expr -> do
reports <- qcCmd QCRandom (T.unpack expr)
reply rep (RRCheck reports)
RCExhaust expr -> do
reports <- qcCmd QCExhaust (T.unpack expr)
reply rep (RRExhaust reports)
RCProve expr -> do
result <- onlineProveSat False (T.unpack expr) Nothing
case result of
AllSatResult [cex] ->
reply rep (RRProve (Just (map (\(_,_,v) -> v) cex)))
ThmResult _ ->
reply rep (RRProve Nothing)
ProverError err ->
reply rep (RRProverError err)
_ ->
reply rep (RRProverError "unexpected prover result")
RCSat expr -> do
result <- onlineProveSat True (T.unpack expr) Nothing
case result of
AllSatResult sas ->
reply rep (RRSat (map (map (\(_,_,v) -> v)) sas))
ThmResult _ ->
reply rep (RRSat [])
ProverError err ->
reply rep (RRProverError err)
_ ->
reply rep (RRProverError "unexpected prover result")
RCLoadPrelude -> do
loadPrelude
reply rep RROk
RCLoadModule fp -> do
loadCmd fp
reply rep RROk
RCDecls -> do
(decls, _namingEnv, _nameDisp) <- getFocusedEnv
reply rep (RRDecls decls)
RCUnknownCmd cmd -> reply rep (RRUnknownCmd cmd)
RCExit -> do
reply rep RROk
io $ close rep
io $ putStrLn "[cryptol-worker] shutting down"
void $ forever loop
withCapturedOutput :: REPL a -> REPL (a, String)
withCapturedOutput m = do
old <- getPutStr
buf <- io $ newIORef ""
setPutStr $ \s -> modifyIORef' buf (++ s)
x <- m
s <- io $ readIORef buf
setPutStr old
return (x, s)
data Server = Server { serverPort :: Word16
, serverMaskSIGINT :: Bool }
deriving Show
main :: IO ()
main = execParser opts >>= mainWith
where
opts =
info (helper <*> serverOpts)
( fullDesc
<> progDesc "Run Cryptol as a server via ZeroMQ and JSON"
<> header "cryptol-server" )
serverOpts =
Server
<$> option auto
( long "port"
<> short 'p'
<> metavar "PORT"
<> value 5555
<> help "TCP port to bind" )
<*> switch
( long "mask-interrupts"
<> help "Suppress interrupt signals" )
mainWith Server {..} = do
when serverMaskSIGINT $ void $ installHandler sigINT Ignore Nothing
server serverPort
cryptol-2.4.0/cryptol-server/Cryptol/ 0000755 0000000 0000000 00000000000 12737220176 016042 5 ustar 00 0000000 0000000 cryptol-2.4.0/cryptol-server/Cryptol/Aeson.hs 0000644 0000000 0000000 00000017156 12737220176 017455 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Orphan 'FromJSON' and 'ToJSON' instances for certain Cryptol
-- types. Since these are meant to be consumed over a wire, they are
-- mostly focused on base values and interfaces rather than a full
-- serialization of internal ASTs and such.
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wall -fno-warn-orphans -fno-warn-type-defaults #-}
module Cryptol.Aeson where
import Control.Applicative
import Control.Exception
import Data.Aeson
import Data.Aeson.TH
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Cryptol.Eval.Error as E
import qualified Cryptol.Eval.Value as E
import qualified Cryptol.ModuleSystem as M
import qualified Cryptol.ModuleSystem.Monad as M
import qualified Cryptol.ModuleSystem.Renamer as M
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Name
import qualified Cryptol.Parser as P
import qualified Cryptol.Parser.AST as P
import qualified Cryptol.Parser.Lexer as P
import qualified Cryptol.Parser.NoInclude as P
import qualified Cryptol.Parser.NoPat as NoPat
import qualified Cryptol.Parser.Position as P
import Cryptol.REPL.Monad
import qualified Cryptol.Testing.Concrete as Test
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck.InferTypes as T
import Cryptol.Utils.Ident
import Cryptol.Utils.PP hiding (empty)
instance ToJSON Doc where
toJSON = String . T.pack . render
instance ToJSON E.Value where
toJSON = \case
E.VRecord fs -> object
[ "record" .= fs ]
E.VTuple vs -> object
[ "tuple" .= vs ]
E.VBit b -> object
[ "bit" .= b ]
E.VSeq isWord xs -> object
[ "sequence" .= object [ "isWord" .= isWord, "elements" .= xs ] ]
E.VWord w -> object
[ "word" .= w ]
E.VStream _ -> object
[ "stream" .= object [ "@note" .= "streams not supported" ] ]
E.VFun _ -> object
[ "function" .= object [ "@note" .= "functions not supported" ] ]
E.VPoly _ -> object
[ "poly" .= object [ "@note" .= "polymorphic values not supported" ] ]
instance FromJSON E.Value where
parseJSON = withObject "Value" $ \o ->
E.VRecord <$> o .: "record"
<|> E.VTuple <$> o .: "tuple"
<|> E.VBit <$> o .: "bit"
<|> do s <- o .: "sequence"
E.VSeq <$> s .: "isWord" <*> s .: "elements"
<|> E.VWord <$> o .: "word"
<|> error ("unexpected JSON value: " ++ show o)
instance ToJSON P.Token where
toJSON = toJSON . pp
instance ToJSON REPLException where
toJSON = \case
ParseError pe -> object
[ "ParseError" .= pe ]
FileNotFound fp -> object
[ "FileNotFound" .= fp ]
DirectoryNotFound fp -> object
[ "DirectoryNotFound" .= fp ]
NoPatError npe -> object
[ "NoPatError" .= npe ]
NoIncludeError nie -> object
[ "NoIncludeError" .= nie ]
EvalError ee -> object
[ "EvalError" .= ee ]
ModuleSystemError _nameDisp me -> object
[ "ModuleSystemError" .= me ]
EvalPolyError sch -> object
[ "EvalPolyError" .= sch ]
TypeNotTestable ty -> object
[ "TypeNotTestable" .= ty ]
instance ToJSON IOException where
toJSON exn = object
[ "IOException" .= show exn ]
instance ToJSON M.RenamerError where
toJSON err = object
[ "renamerError" .= pp err ]
instance ToJSON T.Error where
toJSON err = object
[ "inferError" .= pp err ]
instance ToJSON E.BV where
toJSON = \case
E.BV w v -> object
[ "bitvector" .= object [ "width" .= w, "value" .= v ] ]
instance FromJSON E.BV where
parseJSON = withObject "BV" $ \o -> do
bv <- o .: "bitvector"
E.BV <$> bv .: "width" <*> bv .: "value"
instance ToJSON Test.TestResult where
toJSON = \case
Test.Pass -> object [ "Pass" .= Null ]
Test.FailFalse args -> object [ "FailFalse" .= args ]
Test.FailError err args -> object
[ "FailError" .= show (pp err), "args" .= args ]
instance (ToJSON v) => ToJSON (M.Map Name v) where
toJSON = toJSON . M.mapKeys (unpackIdent . nameIdent)
{-# INLINE toJSON #-}
$(deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''NameInfo)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''E.EvalError)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.ParseError)
$(deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Position)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Located)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.IncludeError)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Schema)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Type)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.TParam)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Prop)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Named)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Kind)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''NoPat.Error)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''M.ModuleError)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''M.ImportSource)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Import)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.ImportSpec)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Type)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TParam)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Kind)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TVar)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TCon)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.PC)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TC)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.UserTC)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Schema)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TFun)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Selector)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } { fieldLabelModifier = drop 1 } ''T.Fixity)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Pragma)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Assoc)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Name)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''IfaceDecl)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.Newtype)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''T.TySyn)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''IfaceDecls)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Iface)
$(deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Ident)
$(deriveJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Range)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.PName)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''P.Pass)
$(deriveToJSON defaultOptions { sumEncoding = ObjectWithSingleField } ''Test.TestReport)
cryptol-2.4.0/dist/ 0000755 0000000 0000000 00000000000 12737220175 012350 5 ustar 00 0000000 0000000 cryptol-2.4.0/dist/build/ 0000755 0000000 0000000 00000000000 12737220175 013447 5 ustar 00 0000000 0000000 cryptol-2.4.0/dist/build/Cryptol/ 0000755 0000000 0000000 00000000000 12737220175 015103 5 ustar 00 0000000 0000000 cryptol-2.4.0/dist/build/Cryptol/Parser.hs 0000644 0000000 0000000 00000510446 12737220175 016705 0 ustar 00 0000000 0000000 {-# OPTIONS_GHC -w #-}
{-# OPTIONS -fglasgow-exts -cpp #-}
-- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Trustworthy #-}
module Cryptol.Parser
( parseModule
, parseProgram, parseProgramWith
, parseExpr, parseExprWith
, parseDecl, parseDeclWith
, parseDecls, parseDeclsWith
, parseLetDecl, parseLetDeclWith
, parseRepl, parseReplWith
, parseSchema, parseSchemaWith
, parseModName, parseHelpName
, ParseError(..), ppError
, Layout(..)
, Config(..), defaultConfig
, guessPreProc, PreProc(..)
) where
import Control.Applicative as A
import Data.Maybe(fromMaybe)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import qualified Data.Text as ST
import Control.Monad(liftM2,msum)
import Cryptol.Prims.Syntax
import Cryptol.Parser.AST
import Cryptol.Parser.Position
import Cryptol.Parser.LexerUtils hiding (mkIdent)
import Cryptol.Parser.ParserUtils
import Cryptol.Parser.Unlit(PreProc(..), guessPreProc)
import Paths_cryptol
import qualified Data.Array as Happy_Data_Array
import qualified GHC.Exts as Happy_GHC_Exts
import Control.Applicative(Applicative(..))
import Control.Monad (ap)
-- parser produced by Happy Version 1.19.5
newtype HappyAbsSyn t69 = HappyAbsSyn HappyAny
#if __GLASGOW_HASKELL__ >= 607
type HappyAny = Happy_GHC_Exts.Any
#else
type HappyAny = forall a . a
#endif
happyIn15 :: (Module PName) -> (HappyAbsSyn t69)
happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn15 #-}
happyOut15 :: (HappyAbsSyn t69) -> (Module PName)
happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut15 #-}
happyIn16 :: (([Located Import], [TopDecl PName])) -> (HappyAbsSyn t69)
happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn16 #-}
happyOut16 :: (HappyAbsSyn t69) -> (([Located Import], [TopDecl PName]))
happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut16 #-}
happyIn17 :: ([Located Import]) -> (HappyAbsSyn t69)
happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn17 #-}
happyOut17 :: (HappyAbsSyn t69) -> ([Located Import])
happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut17 #-}
happyIn18 :: (Located Import) -> (HappyAbsSyn t69)
happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn18 #-}
happyOut18 :: (HappyAbsSyn t69) -> (Located Import)
happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut18 #-}
happyIn19 :: (Maybe (Located ModName)) -> (HappyAbsSyn t69)
happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn19 #-}
happyOut19 :: (HappyAbsSyn t69) -> (Maybe (Located ModName))
happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut19 #-}
happyIn20 :: (Maybe (Located ImportSpec)) -> (HappyAbsSyn t69)
happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn20 #-}
happyOut20 :: (HappyAbsSyn t69) -> (Maybe (Located ImportSpec))
happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut20 #-}
happyIn21 :: ([LIdent]) -> (HappyAbsSyn t69)
happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn21 #-}
happyOut21 :: (HappyAbsSyn t69) -> ([LIdent])
happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut21 #-}
happyIn22 :: ([Ident] -> ImportSpec) -> (HappyAbsSyn t69)
happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn22 #-}
happyOut22 :: (HappyAbsSyn t69) -> ([Ident] -> ImportSpec)
happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut22 #-}
happyIn23 :: (Program PName) -> (HappyAbsSyn t69)
happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn23 #-}
happyOut23 :: (HappyAbsSyn t69) -> (Program PName)
happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut23 #-}
happyIn24 :: (Program PName) -> (HappyAbsSyn t69)
happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn24 #-}
happyOut24 :: (HappyAbsSyn t69) -> (Program PName)
happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut24 #-}
happyIn25 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn25 #-}
happyOut25 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut25 #-}
happyIn26 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn26 #-}
happyOut26 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut26 #-}
happyIn27 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn27 #-}
happyOut27 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut27 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut27 #-}
happyIn28 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn28 #-}
happyOut28 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut28 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut28 #-}
happyIn29 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn29 #-}
happyOut29 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut29 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut29 #-}
happyIn30 :: ([TopDecl PName]) -> (HappyAbsSyn t69)
happyIn30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn30 #-}
happyOut30 :: (HappyAbsSyn t69) -> ([TopDecl PName])
happyOut30 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut30 #-}
happyIn31 :: (Located String) -> (HappyAbsSyn t69)
happyIn31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn31 #-}
happyOut31 :: (HappyAbsSyn t69) -> (Located String)
happyOut31 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut31 #-}
happyIn32 :: (Maybe (Located String)) -> (HappyAbsSyn t69)
happyIn32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn32 #-}
happyOut32 :: (HappyAbsSyn t69) -> (Maybe (Located String))
happyOut32 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut32 #-}
happyIn33 :: (Decl PName) -> (HappyAbsSyn t69)
happyIn33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn33 #-}
happyOut33 :: (HappyAbsSyn t69) -> (Decl PName)
happyOut33 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut33 #-}
happyIn34 :: (Decl PName) -> (HappyAbsSyn t69)
happyIn34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn34 #-}
happyOut34 :: (HappyAbsSyn t69) -> (Decl PName)
happyOut34 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut34 #-}
happyIn35 :: (Newtype PName) -> (HappyAbsSyn t69)
happyIn35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn35 #-}
happyOut35 :: (HappyAbsSyn t69) -> (Newtype PName)
happyOut35 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut35 #-}
happyIn36 :: ([Named (Type PName)]) -> (HappyAbsSyn t69)
happyIn36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn36 #-}
happyOut36 :: (HappyAbsSyn t69) -> ([Named (Type PName)])
happyOut36 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut36 #-}
happyIn37 :: ([ LPName ]) -> (HappyAbsSyn t69)
happyIn37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn37 #-}
happyOut37 :: (HappyAbsSyn t69) -> ([ LPName ])
happyOut37 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut37 #-}
happyIn38 :: (LPName) -> (HappyAbsSyn t69)
happyIn38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn38 #-}
happyOut38 :: (HappyAbsSyn t69) -> (LPName)
happyOut38 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut38 #-}
happyIn39 :: ([Pattern PName]) -> (HappyAbsSyn t69)
happyIn39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn39 #-}
happyOut39 :: (HappyAbsSyn t69) -> ([Pattern PName])
happyOut39 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut39 #-}
happyIn40 :: ([Pattern PName]) -> (HappyAbsSyn t69)
happyIn40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn40 #-}
happyOut40 :: (HappyAbsSyn t69) -> ([Pattern PName])
happyOut40 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut40 #-}
happyIn41 :: ([Decl PName]) -> (HappyAbsSyn t69)
happyIn41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn41 #-}
happyOut41 :: (HappyAbsSyn t69) -> ([Decl PName])
happyOut41 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut41 #-}
happyIn42 :: ([Decl PName]) -> (HappyAbsSyn t69)
happyIn42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn42 #-}
happyOut42 :: (HappyAbsSyn t69) -> ([Decl PName])
happyOut42 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut42 #-}
happyIn43 :: ([Decl PName]) -> (HappyAbsSyn t69)
happyIn43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn43 #-}
happyOut43 :: (HappyAbsSyn t69) -> ([Decl PName])
happyOut43 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut43 #-}
happyIn44 :: (ReplInput PName) -> (HappyAbsSyn t69)
happyIn44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn44 #-}
happyOut44 :: (HappyAbsSyn t69) -> (ReplInput PName)
happyOut44 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut44 #-}
happyIn45 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn45 #-}
happyOut45 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut45 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut45 #-}
happyIn46 :: ([(Expr PName, Expr PName)]) -> (HappyAbsSyn t69)
happyIn46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn46 #-}
happyOut46 :: (HappyAbsSyn t69) -> ([(Expr PName, Expr PName)])
happyOut46 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut46 #-}
happyIn47 :: ((Expr PName, Expr PName)) -> (HappyAbsSyn t69)
happyIn47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn47 #-}
happyOut47 :: (HappyAbsSyn t69) -> ((Expr PName, Expr PName))
happyOut47 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut47 #-}
happyIn48 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn48 #-}
happyOut48 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut48 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut48 #-}
happyIn49 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn49 #-}
happyOut49 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut49 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut49 #-}
happyIn50 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn50 #-}
happyOut50 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut50 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut50 #-}
happyIn51 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn51 #-}
happyOut51 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut51 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut51 #-}
happyIn52 :: (LPName) -> (HappyAbsSyn t69)
happyIn52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn52 #-}
happyOut52 :: (HappyAbsSyn t69) -> (LPName)
happyOut52 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut52 #-}
happyIn53 :: (LPName) -> (HappyAbsSyn t69)
happyIn53 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn53 #-}
happyOut53 :: (HappyAbsSyn t69) -> (LPName)
happyOut53 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut53 #-}
happyIn54 :: (LPName) -> (HappyAbsSyn t69)
happyIn54 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn54 #-}
happyOut54 :: (HappyAbsSyn t69) -> (LPName)
happyOut54 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut54 #-}
happyIn55 :: ([LPName]) -> (HappyAbsSyn t69)
happyIn55 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn55 #-}
happyOut55 :: (HappyAbsSyn t69) -> ([LPName])
happyOut55 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut55 #-}
happyIn56 :: ([Expr PName]) -> (HappyAbsSyn t69)
happyIn56 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn56 #-}
happyOut56 :: (HappyAbsSyn t69) -> ([Expr PName])
happyOut56 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut56 #-}
happyIn57 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn57 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn57 #-}
happyOut57 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut57 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut57 #-}
happyIn58 :: ([(Bool, Integer)]) -> (HappyAbsSyn t69)
happyIn58 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn58 #-}
happyOut58 :: (HappyAbsSyn t69) -> ([(Bool, Integer)])
happyOut58 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut58 #-}
happyIn59 :: ((Bool, Integer)) -> (HappyAbsSyn t69)
happyIn59 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn59 #-}
happyOut59 :: (HappyAbsSyn t69) -> ((Bool, Integer))
happyOut59 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut59 #-}
happyIn60 :: (Located Selector) -> (HappyAbsSyn t69)
happyIn60 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn60 #-}
happyOut60 :: (HappyAbsSyn t69) -> (Located Selector)
happyOut60 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut60 #-}
happyIn61 :: ([Expr PName]) -> (HappyAbsSyn t69)
happyIn61 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn61 #-}
happyOut61 :: (HappyAbsSyn t69) -> ([Expr PName])
happyOut61 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut61 #-}
happyIn62 :: (Named (Expr PName)) -> (HappyAbsSyn t69)
happyIn62 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn62 #-}
happyOut62 :: (HappyAbsSyn t69) -> (Named (Expr PName))
happyOut62 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut62 #-}
happyIn63 :: ([Named (Expr PName)]) -> (HappyAbsSyn t69)
happyIn63 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn63 #-}
happyOut63 :: (HappyAbsSyn t69) -> ([Named (Expr PName)])
happyOut63 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut63 #-}
happyIn64 :: (Expr PName) -> (HappyAbsSyn t69)
happyIn64 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn64 #-}
happyOut64 :: (HappyAbsSyn t69) -> (Expr PName)
happyOut64 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut64 #-}
happyIn65 :: ([[Match PName]]) -> (HappyAbsSyn t69)
happyIn65 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn65 #-}
happyOut65 :: (HappyAbsSyn t69) -> ([[Match PName]])
happyOut65 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut65 #-}
happyIn66 :: ([Match PName]) -> (HappyAbsSyn t69)
happyIn66 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn66 #-}
happyOut66 :: (HappyAbsSyn t69) -> ([Match PName])
happyOut66 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut66 #-}
happyIn67 :: (Match PName) -> (HappyAbsSyn t69)
happyIn67 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn67 #-}
happyOut67 :: (HappyAbsSyn t69) -> (Match PName)
happyOut67 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut67 #-}
happyIn68 :: (Pattern PName) -> (HappyAbsSyn t69)
happyIn68 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn68 #-}
happyOut68 :: (HappyAbsSyn t69) -> (Pattern PName)
happyOut68 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut68 #-}
happyIn69 :: t69 -> (HappyAbsSyn t69)
happyIn69 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn69 #-}
happyOut69 :: (HappyAbsSyn t69) -> t69
happyOut69 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut69 #-}
happyIn70 :: (Pattern PName) -> (HappyAbsSyn t69)
happyIn70 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn70 #-}
happyOut70 :: (HappyAbsSyn t69) -> (Pattern PName)
happyOut70 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut70 #-}
happyIn71 :: ([Pattern PName]) -> (HappyAbsSyn t69)
happyIn71 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn71 #-}
happyOut71 :: (HappyAbsSyn t69) -> ([Pattern PName])
happyOut71 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut71 #-}
happyIn72 :: (Named (Pattern PName)) -> (HappyAbsSyn t69)
happyIn72 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn72 #-}
happyOut72 :: (HappyAbsSyn t69) -> (Named (Pattern PName))
happyOut72 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut72 #-}
happyIn73 :: ([Named (Pattern PName)]) -> (HappyAbsSyn t69)
happyIn73 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn73 #-}
happyOut73 :: (HappyAbsSyn t69) -> ([Named (Pattern PName)])
happyOut73 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut73 #-}
happyIn74 :: (Schema PName) -> (HappyAbsSyn t69)
happyIn74 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn74 #-}
happyOut74 :: (HappyAbsSyn t69) -> (Schema PName)
happyOut74 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut74 #-}
happyIn75 :: (Located [TParam PName]) -> (HappyAbsSyn t69)
happyIn75 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn75 #-}
happyOut75 :: (HappyAbsSyn t69) -> (Located [TParam PName])
happyOut75 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut75 #-}
happyIn76 :: (Located [Prop PName]) -> (HappyAbsSyn t69)
happyIn76 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn76 #-}
happyOut76 :: (HappyAbsSyn t69) -> (Located [Prop PName])
happyOut76 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut76 #-}
happyIn77 :: (Located Kind) -> (HappyAbsSyn t69)
happyIn77 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn77 #-}
happyOut77 :: (HappyAbsSyn t69) -> (Located Kind)
happyOut77 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut77 #-}
happyIn78 :: (TParam PName) -> (HappyAbsSyn t69)
happyIn78 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn78 #-}
happyOut78 :: (HappyAbsSyn t69) -> (TParam PName)
happyOut78 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut78 #-}
happyIn79 :: ([TParam PName]) -> (HappyAbsSyn t69)
happyIn79 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn79 #-}
happyOut79 :: (HappyAbsSyn t69) -> ([TParam PName])
happyOut79 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut79 #-}
happyIn80 :: (TParam PName) -> (HappyAbsSyn t69)
happyIn80 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn80 #-}
happyOut80 :: (HappyAbsSyn t69) -> (TParam PName)
happyOut80 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut80 #-}
happyIn81 :: ([TParam PName]) -> (HappyAbsSyn t69)
happyIn81 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn81 #-}
happyOut81 :: (HappyAbsSyn t69) -> ([TParam PName])
happyOut81 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut81 #-}
happyIn82 :: (Type PName) -> (HappyAbsSyn t69)
happyIn82 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn82 #-}
happyOut82 :: (HappyAbsSyn t69) -> (Type PName)
happyOut82 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut82 #-}
happyIn83 :: (Type PName) -> (HappyAbsSyn t69)
happyIn83 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn83 #-}
happyOut83 :: (HappyAbsSyn t69) -> (Type PName)
happyOut83 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut83 #-}
happyIn84 :: (Type PName) -> (HappyAbsSyn t69)
happyIn84 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn84 #-}
happyOut84 :: (HappyAbsSyn t69) -> (Type PName)
happyOut84 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut84 #-}
happyIn85 :: ([ Type PName ]) -> (HappyAbsSyn t69)
happyIn85 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn85 #-}
happyOut85 :: (HappyAbsSyn t69) -> ([ Type PName ])
happyOut85 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut85 #-}
happyIn86 :: (Located [Type PName]) -> (HappyAbsSyn t69)
happyIn86 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn86 #-}
happyOut86 :: (HappyAbsSyn t69) -> (Located [Type PName])
happyOut86 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut86 #-}
happyIn87 :: ([Type PName]) -> (HappyAbsSyn t69)
happyIn87 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn87 #-}
happyOut87 :: (HappyAbsSyn t69) -> ([Type PName])
happyOut87 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut87 #-}
happyIn88 :: (Named (Type PName)) -> (HappyAbsSyn t69)
happyIn88 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn88 #-}
happyOut88 :: (HappyAbsSyn t69) -> (Named (Type PName))
happyOut88 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut88 #-}
happyIn89 :: ([Named (Type PName)]) -> (HappyAbsSyn t69)
happyIn89 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn89 #-}
happyOut89 :: (HappyAbsSyn t69) -> ([Named (Type PName)])
happyOut89 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut89 #-}
happyIn90 :: (Located Ident) -> (HappyAbsSyn t69)
happyIn90 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn90 #-}
happyOut90 :: (HappyAbsSyn t69) -> (Located Ident)
happyOut90 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut90 #-}
happyIn91 :: (LPName) -> (HappyAbsSyn t69)
happyIn91 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn91 #-}
happyOut91 :: (HappyAbsSyn t69) -> (LPName)
happyOut91 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut91 #-}
happyIn92 :: (Located ModName) -> (HappyAbsSyn t69)
happyIn92 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn92 #-}
happyOut92 :: (HappyAbsSyn t69) -> (Located ModName)
happyOut92 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut92 #-}
happyIn93 :: (Located PName) -> (HappyAbsSyn t69)
happyIn93 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn93 #-}
happyOut93 :: (HappyAbsSyn t69) -> (Located PName)
happyOut93 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut93 #-}
happyIn94 :: (Located PName) -> (HappyAbsSyn t69)
happyIn94 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn94 #-}
happyOut94 :: (HappyAbsSyn t69) -> (Located PName)
happyOut94 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut94 #-}
happyIn95 :: (Type PName) -> (HappyAbsSyn t69)
happyIn95 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn95 #-}
happyOut95 :: (HappyAbsSyn t69) -> (Type PName)
happyOut95 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut95 #-}
happyIn96 :: (Named (Type PName)) -> (HappyAbsSyn t69)
happyIn96 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn96 #-}
happyOut96 :: (HappyAbsSyn t69) -> (Named (Type PName))
happyOut96 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut96 #-}
happyIn97 :: ([Named (Type PName)]) -> (HappyAbsSyn t69)
happyIn97 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn97 #-}
happyOut97 :: (HappyAbsSyn t69) -> ([Named (Type PName)])
happyOut97 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut97 #-}
happyInTok :: (Located Token) -> (HappyAbsSyn t69)
happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyInTok #-}
happyOutTok :: (HappyAbsSyn t69) -> (Located Token)
happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOutTok #-}
happyActOffsets :: HappyAddr
happyActOffsets = HappyA# "\xf9\xff\xc9\x01\xe1\x03\xd1\x02\xa8\x06\xa8\x06\xdf\x03\xf6\x03\xa2\x02\x00\x06\x36\x08\x0d\x03\xf7\x03\x36\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcc\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcc\x03\x00\x00\xcc\x03\xde\x05\xde\x05\x49\x08\xd8\x03\x00\x00\xd2\x05\xb0\x05\x00\x00\x00\x00\xa4\x05\xec\x04\x77\x07\x00\x00\x00\x00\xcb\x03\xf0\x03\x00\x00\x00\x00\x3b\x08\x00\x00\x28\x07\xde\x03\x00\x00\x00\x00\x00\x00\x00\x00\xf8\x06\xd1\x02\x73\x02\x7f\x01\xc6\x06\x05\x00\x6e\x07\xf8\x06\xea\x02\xea\x02\xc5\x03\xc5\x03\x3a\x06\xd9\x03\x89\x00\xf8\x06\xdd\x01\x65\x01\xbd\x03\x46\x01\xf9\x03\xed\x03\xec\x03\x38\x05\x10\x03\x19\x03\x29\x06\x00\x00\xad\x03\x09\x00\xad\x03\x2c\x02\xad\x03\xb5\x01\xbf\x03\x00\x00\x00\x00\xc8\x03\x00\x00\xdc\x03\x00\x00\xa2\x03\xf1\x01\xab\x03\x4e\x01\x00\x00\x0f\x01\x00\x00\x00\x00\x00\x00\x94\x06\x50\x01\x00\x00\x36\x08\x9e\x03\x00\x00\x9a\x07\x00\x00\xa0\x03\x71\x02\x00\x00\x6e\x00\x00\x00\x7a\x02\x8d\x03\x00\x00\x7c\x03\xb7\x03\xf6\xff\x00\x00\xb5\x03\x00\x00\xe4\x06\x00\x00\xfc\x01\x31\x00\x00\x00\x56\x07\x18\x09\x18\x09\x18\x09\xf8\x06\xd1\x02\xf8\x06\x85\x03\x6d\x03\xf8\x06\xda\x01\x97\x07\x82\x05\x00\x00\x00\x00\xfe\x01\x00\x00\x00\x00\x00\x00\x64\x03\x00\x00\x00\x00\x00\x00\x76\x05\xc5\x04\xe7\xff\x00\x00\x00\x00\x53\x03\x00\x00\x00\x00\x6f\x02\xd0\x06\x00\x00\x07\x02\x65\x03\xb3\x03\x00\x00\xea\x02\xea\x02\xbe\x01\x60\x03\x58\x03\x00\x00\xff\x00\x27\x00\x00\x00\x35\x00\xf8\x06\x32\x03\x54\x03\xea\x02\x76\x05\x00\x00\x63\x02\x00\x00\x44\x02\x43\x03\x95\x07\xa3\x07\xa7\x03\x00\x00\xa5\x01\x75\x07\x00\x00\x54\x05\x00\x00\x48\x05\x00\x00\x48\x05\x48\x05\x48\x05\x00\x00\x18\x09\x48\x05\x49\x08\x41\x03\x57\x03\x2d\x03\x00\x00\x18\x09\x00\x00\x18\x09\x62\x07\x54\x07\x00\x00\x03\x07\x0b\x03\x00\x00\x00\x00\x48\x05\x00\x00\x48\x05\x67\x02\x38\x05\x00\x00\x38\x05\x00\x00\x18\x09\x00\x00\x00\x00\x00\x00\x00\x00\x37\x03\xd1\x02\xd1\x02\xd1\x02\xd1\x02\x00\x00\xd1\x02\xd1\x02\x00\x00\xf8\x06\xd1\x02\x00\x00\x00\x00\x00\x00\xd1\x02\x22\x03\xd1\x02\x38\x05\x00\x00\x47\x03\x00\x00\x75\x00\xc6\x07\x30\x02\x0f\x03\x00\x00\x52\x01\x00\x00\xae\x07\xd1\x02\x80\x06\x00\x00\x80\x06\x00\x00\x00\x00\x00\x00\x18\x09\xdd\xff\xd1\x02\x00\x00\xfa\x02\x13\x03\x03\x03\x00\x00\xfd\x02\xfd\x02\xfd\x02\x00\x00\x4c\x07\x00\x00\x38\x05\x48\x05\x00\x00\xf8\x06\x00\x00\xf8\x06\x00\x00\x48\x05\x00\x00\xe4\x02\xf8\x06\x38\x05\x00\x00\x6c\x06\x1d\x06\x40\x02\x00\x00\x40\x02\x00\x00\xe5\x02\x18\x09\x40\x02\x00\x03\x00\x00\xc8\x02\x38\x05\xec\x07\x00\x00\xcc\x02\x05\x02\x05\x02\x00\x00\x00\x00\x36\x00\x00\x00\x36\x00\x40\x02\x3c\x07\xbc\x06\x00\x00\x81\x00\xab\x07\xf5\x01\xe0\x02\x26\x05\x00\x00\x00\x00\x02\x01\x00\x00\x4e\x06\x00\x00\x00\x00\x00\x00\xd1\x02\x18\x09\x00\x00\x00\x00\x18\x09\xce\x02\x00\x00\x1a\x05\x18\x09\xd1\x02\xae\x02\x94\x02\x00\x00\x00\x00\x00\x00\x00\x00\x38\x05\x00\x00\x1a\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x02\xd1\x02\xa0\x02\x25\x02\x7f\x02\x70\x02\x00\x00\x5e\x02\x5b\x02\x5b\x02\x5b\x02\x00\x00\x00\x00\x5b\x02\xd1\x02\x00\x00\x2e\x02\x00\x00\x00\x00\x18\x09\x00\x00\x00\x00\x18\x09\x18\x09\x1a\x05\x00\x00\x03\x07\xf1\x01\x22\x02\xcd\x00\x1b\x02\xd1\x02\xf8\x06\xf8\x06\xd1\x02\x00\x00\x1b\x02\x18\x09\x1f\x02\x00\x00\x00\x00\xe1\x01\x00\x00\x18\x09\xcd\x00\xe1\x01\x00\x00\x00\x00\x00\x00\x00\x02\x00\x00\x00\x00\x00\x00\xcf\x01\x00\x00\xbc\x01\xd1\x02\xda\x02\xa7\x01\xcb\x00\x00\x00\x00\x00\x86\x01\xa7\x01\xae\x01\xd1\x02\x38\x05\xf8\x04\x9a\x01\x9e\x01\x89\x01\x00\x00\x6a\x01\x00\x00\x00\x00\x00\x00\x9a\x03\x00\x00\x6a\x01\x00\x00\xa4\x00\x00\x00\x00\x00\x00\x00\x38\x05\x00\x00\x00\x00"#
happyGotoOffsets :: HappyAddr
happyGotoOffsets = HappyA# "\x6f\x01\x63\x00\x39\x01\x9a\x04\x5b\x01\x11\x01\x0a\x01\x26\x01\xec\x00\xeb\x07\xdb\x02\x1a\x00\x00\x00\x7c\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\xf3\x08\x87\x03\x00\x00\x00\x00\x4f\x03\xbf\x02\x00\x00\x00\x00\xe7\x08\x3f\x08\x83\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x03\x00\x00\x0c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbb\x01\x5a\x03\x42\x03\x34\x03\x1f\x00\x78\x03\x49\x01\xe1\x00\xe9\x04\xac\x04\x00\x00\x00\x00\x07\x01\x00\x00\x00\x00\xb7\x00\x55\x01\x00\x00\xda\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x03\x70\x06\x60\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x00\x00\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2f\x01\xd4\x00\x00\x00\x4b\x02\x00\x00\x00\x00\xe2\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x16\x01\x00\x00\x00\x00\x00\x00\x00\x00\x1c\x02\x7a\x03\x4e\x03\xb9\x02\xe3\x00\x8d\x04\x4f\x01\x00\x00\x00\x00\x9e\x00\x00\x00\xf0\xff\xde\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdb\x08\x18\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xab\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x65\x02\x37\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x76\x00\xdc\xff\x00\x00\x08\x02\xcf\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf5\x02\x00\x00\x00\x00\x64\x02\xf5\x02\x00\x00\xb1\x02\x00\x00\xc3\x08\x00\x00\xb7\x08\xab\x08\x23\x03\x00\x00\xf5\x02\x9f\x08\xf5\x02\x00\x00\x00\x00\x00\x00\x00\x00\xf5\x02\x00\x00\xf5\x02\xf5\x02\xf5\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x93\x08\x00\x00\x87\x08\x0c\x08\x36\x02\x00\x00\x71\x00\x00\x00\xf5\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x74\x04\xec\x05\x68\x03\x67\x04\x00\x00\x5a\x04\x41\x04\x00\x00\x88\x07\x34\x04\x00\x00\x00\x00\x00\x00\x27\x04\x00\x00\x0e\x04\xeb\xff\x00\x00\x00\x00\x00\x00\xcc\x00\xf5\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf5\x02\x9b\x02\x2d\x01\x00\x00\x1e\x01\x00\x00\x00\x00\x00\x00\xb6\x02\x00\x00\x01\x04\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x01\x00\x00\x42\x00\x7b\x08\x00\x00\xc0\x06\x00\x00\xbb\x06\x00\x00\x6f\x08\x00\x00\x00\x00\xba\x00\xd2\xff\x00\x00\x05\x01\x2c\x00\xd5\x00\x00\x00\xbc\x00\x00\x00\x00\x00\xaa\x02\x90\x00\xd6\x00\x00\x00\x00\x00\xd7\x01\x6c\x02\x00\x00\x00\x00\x45\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x00\xfb\x01\x48\x00\x00\x00\x39\x02\x57\x01\x00\x00\x00\x00\xd1\x07\x00\x00\x00\x00\x00\x00\x00\x00\x13\x01\x00\x00\x00\x00\x00\x00\xf4\x03\x4c\x02\x00\x00\x00\x00\x4c\x02\x00\x00\x00\x00\x63\x08\x3c\x02\xdb\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x57\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x03\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc1\x03\x00\x00\x00\x00\x00\x00\x00\x00\xf4\x01\x00\x00\x00\x00\xf4\x01\xf4\x01\x4b\x08\x00\x00\x00\x00\x01\x00\x00\x00\x93\x00\x00\x00\xa8\x03\x49\x06\x92\x01\x9b\x03\x00\x00\x00\x00\xf4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf4\x01\x33\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x03\x0e\x01\x4f\x00\x00\x00\x00\x00\x00\x00\x2b\x01\x1b\x00\x00\x00\x75\x03\xfb\xff\xc4\x07\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe0\xff\x00\x00\x00\x00"#
happyDefActions :: HappyAddr
happyDefActions = HappyA# "\x00\x00\xc5\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x10\xff\x91\xff\x8f\xff\x16\xff\x13\xff\x11\xff\x00\x00\x1b\xff\x12\xff\x18\xff\x17\xff\x19\xff\x1a\xff\x00\x00\x8d\xff\x8e\xff\x8a\xff\x8c\xff\x8b\xff\x89\xff\x88\xff\x90\xff\x15\xff\x00\x00\x14\xff\x00\x00\x00\x00\x00\x00\x45\xff\x32\xff\x2f\xff\x00\x00\x2e\xff\x2d\xff\x2c\xff\x00\x00\x00\x00\x00\x00\x25\xff\xa4\xff\x00\x00\xa5\xff\xa3\xff\x9b\xff\x98\xff\x96\xff\x94\xff\x85\xff\x83\xff\x82\xff\x81\xff\x80\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\xff\x00\x00\x00\x00\x55\xff\xb2\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\xff\x00\x00\x00\x00\x00\x00\xc5\xff\x00\x00\xc5\xff\x00\x00\xcc\xff\xc6\xff\x00\x00\xce\xff\x00\x00\xc7\xff\x00\x00\xc5\xff\x00\x00\xef\xff\xea\xff\xee\xff\xd9\xff\xcf\xff\xd0\xff\xc6\xff\x00\x00\xd6\xff\x00\x00\x19\xff\xcd\xff\x00\x00\xdb\xff\x00\x00\x00\x00\xdc\xff\x00\x00\x47\xff\x00\x00\x00\x00\x4c\xff\x00\x00\x00\x00\x57\xff\x55\xff\x00\x00\x54\xff\x00\x00\x52\xff\x00\x00\x00\x00\x4f\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xae\xff\x00\x00\x00\x00\xac\xff\xaa\xff\x00\x00\xa6\xff\x92\xff\x93\xff\x00\x00\x0e\xff\x78\xff\x0d\xff\x00\x00\x00\x00\x00\x00\x73\xff\x71\xff\x70\xff\x75\xff\x68\xff\x00\x00\x00\x00\x7c\xff\x00\x00\x00\x00\x00\x00\x7d\xff\x8c\xff\x8b\xff\x65\xff\x64\xff\x00\x00\x7a\xff\x00\x00\x00\x00\x9e\xff\x00\x00\x54\xff\x00\x00\x84\xff\x00\x00\x00\x00\x3a\xff\x00\x00\x1d\xff\x00\x00\x3c\xff\x41\xff\x00\x00\x00\x00\x29\xff\x00\x00\x00\x00\x24\xff\x30\xff\x2e\xff\x00\x00\x31\xff\x00\x00\x00\x00\x00\x00\x3f\xff\x43\xff\x00\x00\x44\xff\x00\x00\x00\x00\x00\x00\x0f\xff\x42\xff\x33\xff\x34\xff\x00\x00\x00\x00\x23\xff\x22\xff\x00\x00\x27\xff\x28\xff\x00\x00\x2a\xff\x00\x00\x00\x00\x00\x00\x26\xff\x00\x00\x40\xff\x97\xff\x95\xff\x77\xff\x6e\xff\x6d\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x79\xff\x00\x00\x63\xff\x5f\xff\x00\x00\x00\x00\x7e\xff\x76\xff\x7f\xff\x00\x00\x00\x00\x00\x00\x00\x00\x7b\xff\x00\x00\x74\xff\x00\x00\x00\x00\x00\x00\x16\xff\x06\xff\x00\x00\x0b\xff\x00\x00\x00\x00\x00\x00\xa7\xff\x00\x00\xc4\xff\xb3\xff\xb2\xff\x00\x00\xad\xff\x00\x00\xab\xff\x56\xff\xc3\xff\x00\x00\x87\xff\xbb\xff\xbd\xff\xbc\xff\x36\xff\x00\x00\x38\xff\x00\x00\x00\x00\x4d\xff\x00\x00\x4e\xff\x00\x00\x50\xff\x00\x00\x51\xff\xb1\xff\x00\x00\x00\x00\x4b\xff\x00\x00\x00\x00\xc5\xff\xdd\xff\xc5\xff\xda\xff\x00\x00\x00\x00\xc5\xff\xe7\xff\xd1\xff\x00\x00\x00\x00\x00\x00\xd5\xff\x19\xff\xc5\xff\xc5\xff\xf2\xff\xec\xff\xf1\xff\xeb\xff\xf0\xff\xc5\xff\x00\x00\x00\x00\xd4\xff\xe0\xff\x00\x00\x00\x00\x00\x00\x00\x00\xd8\xff\xd7\xff\x00\x00\xa0\xff\x00\x00\xa2\xff\x46\xff\x48\xff\x00\x00\x58\xff\x4a\xff\x49\xff\xbf\xff\x00\x00\x35\xff\x00\x00\x00\x00\x00\x00\xc1\xff\x00\x00\xa9\xff\xa8\xff\x99\xff\x0c\xff\x00\x00\x0a\xff\x00\x00\x08\xff\x09\xff\x72\xff\x6f\xff\x67\xff\x6a\xff\x00\x00\x6c\xff\x6c\xff\x66\xff\x5d\xff\x5b\xff\x00\x00\x62\xff\x6b\xff\x9c\xff\x9d\xff\x9a\xff\xba\xff\x00\x00\x39\xff\x3c\xff\x1c\xff\x3b\xff\x1e\xff\x3d\xff\x3e\xff\x20\xff\x1f\xff\x00\x00\x2b\xff\x21\xff\xc5\xff\x00\x00\x00\x00\xb9\xff\x00\x00\x00\x00\x00\x00\x61\xff\x5e\xff\x69\xff\x07\xff\x00\x00\x05\xff\xb1\xff\xc0\xff\x86\xff\xbe\xff\x00\x00\xc2\xff\xa1\xff\x9f\xff\xc9\xff\x00\x00\xcb\xff\xe8\xff\xe9\xff\x00\x00\xe1\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xca\xff\xb8\xff\x00\x00\x00\x00\xd2\xff\x00\x00\xe2\xff\x00\x00\x00\x00\x60\xff\x5c\xff\x5a\xff\x59\xff\xf3\xff\x37\xff\xc8\xff\x00\x00\xe3\xff\xd3\xff\xb7\xff\x00\x00\xb6\xff\xb5\xff\xe6\xff\x00\x00\xe4\xff"#
happyCheck :: HappyAddr
happyCheck = HappyA# "\xff\xff\x06\x00\x01\x00\x02\x00\x03\x00\x28\x00\x01\x00\x17\x00\x2b\x00\x2d\x00\x11\x00\x39\x00\x0b\x00\x0c\x00\x27\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x01\x00\x02\x00\x03\x00\x16\x00\x17\x00\x32\x00\x2f\x00\x12\x00\x17\x00\x4b\x00\x0b\x00\x0c\x00\x2a\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x03\x00\x4b\x00\x2f\x00\x16\x00\x17\x00\x4b\x00\x27\x00\x37\x00\x0b\x00\x0c\x00\x15\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x4b\x00\x36\x00\x37\x00\x16\x00\x17\x00\x4b\x00\x4c\x00\x16\x00\x12\x00\x25\x00\x26\x00\x27\x00\x16\x00\x17\x00\x3b\x00\x1e\x00\x4b\x00\x1b\x00\x03\x00\x36\x00\x37\x00\x1a\x00\x4b\x00\x4c\x00\x2f\x00\x30\x00\x0b\x00\x0c\x00\x21\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x22\x00\x36\x00\x37\x00\x16\x00\x17\x00\x28\x00\x4b\x00\x4c\x00\x18\x00\x19\x00\x36\x00\x37\x00\x15\x00\x4b\x00\x4c\x00\x31\x00\x4e\x00\x4f\x00\x4b\x00\x08\x00\x37\x00\x0a\x00\x4b\x00\x4c\x00\x0d\x00\x3e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x01\x00\x4b\x00\x4c\x00\x16\x00\x17\x00\x36\x00\x37\x00\x0b\x00\x0c\x00\x37\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x4b\x00\x26\x00\x27\x00\x16\x00\x17\x00\x09\x00\x51\x00\x17\x00\x4b\x00\x18\x00\x19\x00\x4b\x00\x4c\x00\x24\x00\x4b\x00\x4c\x00\x35\x00\x36\x00\x37\x00\x38\x00\x36\x00\x37\x00\x0b\x00\x0c\x00\x2f\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x22\x00\x39\x00\x3a\x00\x16\x00\x17\x00\x36\x00\x37\x00\x21\x00\x4b\x00\x4c\x00\x37\x00\x4b\x00\x4c\x00\x3f\x00\x30\x00\x31\x00\x2a\x00\x0b\x00\x0c\x00\x4b\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x4b\x00\x4b\x00\x4c\x00\x16\x00\x17\x00\x4b\x00\x4c\x00\x18\x00\x19\x00\x21\x00\x36\x00\x37\x00\x0c\x00\x25\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x18\x00\x19\x00\x3e\x00\x16\x00\x17\x00\x0d\x00\x37\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x04\x00\x4b\x00\x4c\x00\x16\x00\x17\x00\x36\x00\x37\x00\x0c\x00\x37\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x14\x00\x4b\x00\x4c\x00\x16\x00\x17\x00\x22\x00\x37\x00\x35\x00\x36\x00\x37\x00\x36\x00\x37\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x2c\x00\x18\x00\x19\x00\x30\x00\x31\x00\x36\x00\x37\x00\x13\x00\x33\x00\x27\x00\x4b\x00\x4c\x00\x37\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x1d\x00\x1e\x00\x36\x00\x37\x00\x21\x00\x22\x00\x23\x00\x24\x00\x12\x00\x4b\x00\x4c\x00\x15\x00\x29\x00\x2a\x00\x12\x00\x37\x00\x12\x00\x37\x00\x16\x00\x17\x00\x16\x00\x17\x00\x1a\x00\x4b\x00\x4c\x00\x1b\x00\x12\x00\x22\x00\x12\x00\x1c\x00\x16\x00\x17\x00\x16\x00\x17\x00\x1a\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x12\x00\x22\x00\x30\x00\x31\x00\x16\x00\x17\x00\x2a\x00\x4b\x00\x4c\x00\x13\x00\x4e\x00\x36\x00\x37\x00\x36\x00\x37\x00\x12\x00\x31\x00\x12\x00\x09\x00\x16\x00\x17\x00\x16\x00\x17\x00\x36\x00\x37\x00\x36\x00\x37\x00\x35\x00\x36\x00\x37\x00\x38\x00\x41\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x36\x00\x37\x00\x06\x00\x4b\x00\x4c\x00\x4b\x00\x4e\x00\x0b\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x10\x00\x4b\x00\x4c\x00\x36\x00\x37\x00\x36\x00\x37\x00\x12\x00\x18\x00\x4b\x00\x4c\x00\x16\x00\x17\x00\x12\x00\x28\x00\x00\x00\x22\x00\x16\x00\x17\x00\x21\x00\x49\x00\x4a\x00\x4b\x00\x25\x00\x4b\x00\x4c\x00\x4b\x00\x4c\x00\x12\x00\x37\x00\x38\x00\x31\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x36\x00\x37\x00\x08\x00\x09\x00\x0a\x00\x04\x00\x36\x00\x37\x00\x28\x00\x08\x00\x09\x00\x0a\x00\x36\x00\x37\x00\x14\x00\x4b\x00\x4c\x00\x17\x00\x4e\x00\x19\x00\x50\x00\x4b\x00\x4c\x00\x37\x00\x17\x00\x1f\x00\x20\x00\x4b\x00\x4c\x00\x4b\x00\x24\x00\x4d\x00\x26\x00\x4b\x00\x4c\x00\x29\x00\x04\x00\x21\x00\x25\x00\x2d\x00\x08\x00\x09\x00\x0a\x00\x12\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x04\x00\x20\x00\x06\x00\x17\x00\x08\x00\x09\x00\x0a\x00\x12\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x25\x00\x24\x00\x17\x00\x04\x00\x19\x00\x06\x00\x12\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x1c\x00\x1d\x00\x1e\x00\x4b\x00\x4c\x00\x21\x00\x17\x00\x04\x00\x19\x00\x2e\x00\x28\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x1f\x00\x3a\x00\x3b\x00\x36\x00\x37\x00\x12\x00\x17\x00\x04\x00\x19\x00\x2e\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x28\x00\x3a\x00\x3b\x00\x2b\x00\x4b\x00\x4c\x00\x17\x00\x04\x00\x19\x00\x2e\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x1a\x00\x22\x00\x3b\x00\x12\x00\x26\x00\x27\x00\x17\x00\x21\x00\x19\x00\x2e\x00\x22\x00\x30\x00\x4b\x00\x4c\x00\x1f\x00\x30\x00\x31\x00\x20\x00\x21\x00\x24\x00\x2a\x00\x3a\x00\x24\x00\x12\x00\x30\x00\x31\x00\x04\x00\x29\x00\x2a\x00\x2e\x00\x08\x00\x09\x00\x0a\x00\x12\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x41\x00\x42\x00\x05\x00\x3a\x00\x07\x00\x1c\x00\x1d\x00\x17\x00\x04\x00\x19\x00\x4b\x00\x28\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x21\x00\x30\x00\x4b\x00\x4c\x00\x25\x00\x4e\x00\x17\x00\x2a\x00\x19\x00\x2e\x00\x24\x00\x30\x00\x41\x00\x42\x00\x1f\x00\x29\x00\x2a\x00\x26\x00\x27\x00\x24\x00\x21\x00\x3a\x00\x4b\x00\x01\x00\x25\x00\x03\x00\x04\x00\x05\x00\x12\x00\x2e\x00\x08\x00\x09\x00\x0a\x00\x26\x00\x27\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x1b\x00\x3a\x00\x08\x00\x09\x00\x0a\x00\x17\x00\x49\x00\x19\x00\x4b\x00\x4b\x00\x4c\x00\x21\x00\x4e\x00\x1f\x00\x14\x00\x25\x00\x24\x00\x17\x00\x24\x00\x19\x00\x1a\x00\x29\x00\x2a\x00\x21\x00\x21\x00\x1f\x00\x22\x00\x25\x00\x2e\x00\x4b\x00\x24\x00\x4d\x00\x26\x00\x33\x00\x21\x00\x29\x00\x1e\x00\x37\x00\x25\x00\x2d\x00\x30\x00\x31\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x35\x00\x36\x00\x08\x00\x09\x00\x0a\x00\x49\x00\x4a\x00\x4b\x00\x4b\x00\x4c\x00\x12\x00\x4e\x00\x20\x00\x13\x00\x14\x00\x4b\x00\x4c\x00\x17\x00\x4e\x00\x19\x00\x21\x00\x22\x00\x23\x00\x24\x00\x12\x00\x1f\x00\x3f\x00\x40\x00\x29\x00\x2a\x00\x24\x00\x4b\x00\x26\x00\x4d\x00\x02\x00\x29\x00\x49\x00\x4a\x00\x4b\x00\x2d\x00\x26\x00\x27\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x35\x00\x36\x00\x08\x00\x09\x00\x0a\x00\x26\x00\x27\x00\x04\x00\x26\x00\x27\x00\x28\x00\x08\x00\x09\x00\x0a\x00\x14\x00\x4b\x00\x4c\x00\x17\x00\x4e\x00\x19\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x1f\x00\x17\x00\x08\x00\x09\x00\x0a\x00\x24\x00\x45\x00\x26\x00\x2a\x00\x1f\x00\x29\x00\x2f\x00\x4b\x00\x4c\x00\x2d\x00\x4e\x00\x20\x00\x17\x00\x28\x00\x19\x00\x45\x00\x46\x00\x35\x00\x36\x00\x08\x00\x1f\x00\x4b\x00\x4c\x00\x28\x00\x4e\x00\x24\x00\x2a\x00\x26\x00\x04\x00\x05\x00\x29\x00\x04\x00\x08\x00\x09\x00\x0a\x00\x08\x00\x09\x00\x0a\x00\x26\x00\x27\x00\x04\x00\x21\x00\x35\x00\x36\x00\x08\x00\x09\x00\x0a\x00\x17\x00\x12\x00\x4b\x00\x17\x00\x4d\x00\x19\x00\x1a\x00\x28\x00\x1f\x00\x4b\x00\x4c\x00\x1f\x00\x17\x00\x37\x00\x19\x00\x01\x00\x24\x00\x2a\x00\x04\x00\x28\x00\x1f\x00\x20\x00\x08\x00\x09\x00\x0a\x00\x24\x00\x2e\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x2e\x00\x01\x00\x17\x00\x28\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x1e\x00\x4b\x00\x4c\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x2f\x00\x29\x00\x2a\x00\x28\x00\x1e\x00\x20\x00\x2e\x00\x21\x00\x22\x00\x23\x00\x24\x00\x44\x00\x45\x00\x12\x00\x47\x00\x29\x00\x2a\x00\x2a\x00\x4b\x00\x4c\x00\x2e\x00\x4e\x00\x1a\x00\x31\x00\x26\x00\x27\x00\x28\x00\x23\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x21\x00\x4e\x00\x29\x00\x2a\x00\x20\x00\x1e\x00\x34\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x2b\x00\x4e\x00\x29\x00\x2a\x00\x1e\x00\x45\x00\x28\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x20\x00\x4e\x00\x29\x00\x2a\x00\x26\x00\x27\x00\x28\x00\x2b\x00\x2c\x00\x4b\x00\x4c\x00\x22\x00\x4e\x00\x25\x00\x26\x00\x27\x00\x1e\x00\x26\x00\x27\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x28\x00\x4e\x00\x29\x00\x2a\x00\x1e\x00\x20\x00\x21\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x22\x00\x4e\x00\x29\x00\x2a\x00\x1e\x00\x20\x00\x21\x00\x21\x00\x22\x00\x23\x00\x24\x00\x2f\x00\x25\x00\x26\x00\x27\x00\x29\x00\x2a\x00\x20\x00\x21\x00\x20\x00\x21\x00\x20\x00\x21\x00\x4b\x00\x4c\x00\x30\x00\x4e\x00\x3b\x00\x02\x00\x1e\x00\x18\x00\x22\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x3b\x00\x4e\x00\x29\x00\x2a\x00\x1e\x00\x01\x00\x01\x00\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\x38\x00\x4e\x00\x29\x00\x2a\x00\x1e\x00\x01\x00\x22\x00\x21\x00\x22\x00\x23\x00\x24\x00\x3b\x00\x23\x00\x12\x00\x2b\x00\x29\x00\x2a\x00\x3b\x00\x3b\x00\x11\x00\x13\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\x2f\x00\x4e\x00\x2f\x00\xff\xff\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\x1e\x00\xff\xff\xff\xff\x21\x00\x22\x00\x23\x00\x24\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x29\x00\x2a\x00\xff\xff\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\x24\x00\x25\x00\xff\xff\xff\xff\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\x2e\x00\x08\x00\x09\x00\x0a\x00\x4b\x00\x4c\x00\x01\x00\x4e\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\x20\x00\x24\x00\xff\xff\x17\x00\x24\x00\x19\x00\x29\x00\x2a\x00\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\x1f\x00\xff\xff\xff\xff\x04\x00\x17\x00\x24\x00\x19\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\x17\x00\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\xff\xff\x17\x00\x24\x00\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\xff\xff\x17\x00\x24\x00\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\xff\xff\x17\x00\x24\x00\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x01\x00\xff\xff\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\xff\xff\x17\x00\x24\x00\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x2e\x00\x01\x00\x24\x00\x03\x00\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x2e\x00\x21\x00\x22\x00\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\x2a\x00\x17\x00\xff\xff\x19\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\x04\x00\xff\xff\xff\xff\x24\x00\x08\x00\x09\x00\x0a\x00\xff\xff\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x04\x00\x2e\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x17\x00\xff\xff\x19\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\x1f\x00\xff\xff\x04\x00\xff\xff\x17\x00\x24\x00\x08\x00\x09\x00\x0a\x00\xff\xff\x0c\x00\x0d\x00\x0e\x00\x0f\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x25\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x17\x00\xff\xff\x19\x00\x2e\x00\xff\xff\x30\x00\xff\xff\xff\xff\x1f\x00\xff\xff\xff\xff\x04\x00\xff\xff\x24\x00\x25\x00\x08\x00\x09\x00\x0a\x00\xff\xff\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x2e\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x25\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\x35\x00\x36\x00\x37\x00\x38\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x24\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\xff\xff\xff\xff\x04\x00\xff\xff\x24\x00\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\xff\xff\x17\x00\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x28\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\x25\x00\x08\x00\x09\x00\x0a\x00\x1f\x00\x35\x00\x36\x00\x37\x00\xff\xff\x24\x00\x35\x00\x36\x00\x37\x00\x28\x00\xff\xff\xff\xff\x17\x00\x04\x00\x19\x00\x2e\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x20\x00\xff\xff\x4b\x00\x4c\x00\x24\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\xff\xff\x17\x00\xff\xff\x19\x00\x2e\x00\xff\xff\xff\xff\x12\x00\xff\xff\x1f\x00\x15\x00\x16\x00\xff\xff\xff\xff\x24\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\xff\xff\x20\x00\x21\x00\x22\x00\x2e\x00\xff\xff\x25\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x2b\x00\x2c\x00\x08\x00\x09\x00\x0a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\xff\xff\xff\xff\x3b\x00\x17\x00\x04\x00\x19\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x24\x00\xff\xff\x26\x00\xff\xff\x04\x00\x29\x00\xff\xff\x17\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\xff\xff\x04\x00\x1f\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x17\x00\x28\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\xff\xff\x17\x00\x1a\x00\x01\x00\xff\xff\xff\xff\x04\x00\x05\x00\x28\x00\x1f\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x04\x00\x1a\x00\xff\xff\x28\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\xff\xff\x17\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x1f\x00\x17\x00\x1a\x00\xff\xff\xff\xff\x24\x00\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x04\x00\x25\x00\xff\xff\x04\x00\x08\x00\x09\x00\x0a\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x17\x00\x04\x00\x05\x00\x17\x00\xff\xff\x08\x00\x09\x00\x0a\x00\x1f\x00\x22\x00\xff\xff\x1f\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x2b\x00\x2c\x00\x17\x00\x20\x00\x21\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x20\x00\xff\xff\x3b\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\xff\xff\xff\xff\xff\xff\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x21\x00\xff\xff\xff\xff\xff\xff\x25\x00\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\x05\x00\xff\xff\xff\xff\x08\x00\x09\x00\x0a\x00\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x3b\x00\x3c\x00\x3d\x00\xff\xff\x17\x00\xff\xff\xff\xff\xff\xff\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\x3b\x00\x3c\x00\x3d\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\x3b\x00\x3c\x00\x3d\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\x3b\x00\x3c\x00\x3d\x00\x4b\x00\x4c\x00\xff\xff\x4e\x00\xff\xff\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x04\x00\x05\x00\xff\xff\x3d\x00\x08\x00\x09\x00\x0a\x00\xff\xff\xff\xff\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\x3e\x00\x4b\x00\x4c\x00\x17\x00\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\x48\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\x2a\x00\x4e\x00\xff\xff\xff\xff\x51\x00\x52\x00\xff\xff\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x2c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\x48\x00\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x43\x00\x44\x00\x45\x00\xff\xff\x47\x00\xff\xff\xff\xff\xff\xff\x4b\x00\x4c\x00\xff\xff\x4e\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
happyTable :: HappyAddr
happyTable = HappyA# "\x00\x00\xc1\x01\x91\x01\x6e\x00\x6f\x00\xaf\xff\xab\x00\x18\x01\xaf\xff\xf3\x00\x0e\x00\x5b\x01\x70\x00\x71\x00\x0b\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x6d\x00\x6e\x00\x6f\x00\x50\x00\x51\x00\x0c\x01\x74\x01\x80\x00\xac\x00\x82\x00\x70\x00\x71\x00\x30\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x48\x01\xf4\x00\x6d\x00\x50\x00\x51\x00\xca\x01\xad\x00\x96\x00\x49\x01\x71\x00\xc4\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xaf\x00\x53\x00\x54\x00\x50\x00\x51\x00\x11\x00\x19\x01\xf9\x00\x9d\x00\x0e\x00\x0f\x00\x10\x00\x50\x00\x51\x00\xff\xff\xfa\x00\xc2\x01\x57\x01\x4a\x01\x53\x00\x54\x00\x2b\x01\x11\x00\x55\x00\xad\x00\xae\x00\x4b\x01\x71\x00\x2c\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x38\x01\x53\x00\x54\x00\x50\x00\x51\x00\xf8\x00\x11\x00\x55\x00\xac\x01\x98\x00\x53\x00\x54\x00\xb2\x01\x11\x00\x12\x00\x3a\x01\x13\x00\x14\x00\xaf\x00\x62\x00\x96\x00\x63\x00\x11\x00\x55\x00\x64\x00\xb9\x01\x65\x00\x66\x00\x67\x00\x68\x00\xab\x00\x11\x00\x55\x00\x50\x00\x51\x00\x53\x00\x54\x00\xb0\x01\x71\x00\x99\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x9b\x01\x84\x00\x10\x00\x50\x00\x51\x00\xac\x01\x9c\x01\xac\x00\x62\x01\xf6\x00\x98\x00\x11\x00\x55\x00\x36\x01\x11\x00\x89\x00\x85\x00\x86\x00\x87\x00\x88\x00\x53\x00\x54\x00\x52\x01\x71\x00\x37\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\xe5\xff\x80\x00\x81\x00\x50\x00\x51\x00\x53\x00\x54\x00\x9b\x00\x11\x00\x89\x00\x99\x00\x11\x00\x55\x00\x84\x01\xe5\xff\xe5\xff\x9c\x00\x7d\x00\x71\x00\x82\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x85\x01\x11\x00\x55\x00\x50\x00\x51\x00\x11\x00\x89\x00\x05\x01\x98\x00\xee\x00\x53\x00\x54\x00\x55\x01\xc8\x01\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x97\x00\x98\x00\x87\x01\x50\x00\x51\x00\x7c\x00\x1b\x01\x65\x00\x66\x00\x67\x00\x68\x00\x50\x01\x11\x00\x55\x00\x50\x00\x51\x00\x53\x00\x54\x00\x56\x01\x99\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x3f\x01\x11\x00\x89\x00\x50\x00\x51\x00\x38\x01\x99\x00\x5c\x01\x86\x00\x87\x00\x53\x00\x54\x00\x11\x00\x55\x00\x11\x00\x89\x00\x72\x01\xa2\x00\x98\x00\xb2\x01\x3a\x01\x53\x00\x54\x00\x35\x00\x8a\x01\x93\x00\x11\x00\x89\x00\x8b\x01\x11\x00\x89\x00\x11\x00\x55\x00\x36\x00\x37\x00\x53\x00\x54\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x80\x00\x11\x00\x55\x00\xfb\x00\x3c\x00\x3d\x00\x4f\x00\x99\x00\x9d\x00\x20\x01\x50\x00\x51\x00\x50\x00\x51\x00\x59\x01\x11\x00\x55\x00\x9e\x00\x4f\x00\x15\x01\x96\x00\x4d\x00\x50\x00\x51\x00\x50\x00\x51\x00\x52\x00\x11\x00\x89\x00\x11\x00\x89\x00\x69\x01\x38\x01\xa5\x01\x17\x01\x50\x00\x51\x00\xc1\x00\x11\x00\x12\x00\x4c\x00\x3e\x00\x53\x00\x54\x00\x53\x00\x54\x00\x6a\x01\x3a\x01\x43\x01\x60\x00\x50\x00\x51\x00\x50\x00\x51\x00\x53\x00\x54\x00\x53\x00\x54\x00\x85\x00\x86\x00\x87\x00\x88\x00\x63\x01\x11\x00\x55\x00\x11\x00\x55\x00\x53\x00\x54\x00\x41\x01\x11\x00\x12\x00\x27\x01\x3e\x00\x42\x01\x11\x00\x55\x00\x11\x00\x55\x00\x43\x01\x11\x00\x89\x00\x53\x00\x54\x00\x53\x00\x54\x00\x96\x00\x7b\x00\x11\x00\x55\x00\x50\x00\x51\x00\x5e\x00\x54\xff\x6b\x00\x46\x01\x50\x00\x51\x00\x6e\x01\xc6\x00\xc5\x01\xe6\x00\x6f\x01\x11\x00\x55\x00\x11\x00\x55\x00\x80\x00\x54\xff\x54\xff\x47\x01\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x1e\x01\x87\x00\x18\x00\x19\x00\x1a\x00\x16\x00\x53\x00\x54\x00\x95\x00\x18\x00\x19\x00\x1a\x00\x53\x00\x54\x00\x44\x00\x11\x00\x12\x00\x1b\x00\xa3\x00\x45\x00\xa4\x00\x11\x00\x89\x00\x96\x00\x1b\x00\x46\x00\xb5\x00\x11\x00\x55\x00\x24\x00\x47\x00\xa8\x01\x48\x00\x11\x00\x55\x00\x49\x00\x16\x00\x96\x01\xc7\x01\x4a\x00\x18\x00\x19\x00\x1a\x00\x80\x00\x1d\x00\x1e\x00\x1f\x00\xb6\x00\xb7\x00\x22\x00\x23\x00\x24\x00\x16\x00\xc0\x01\x6a\x00\x1b\x00\x18\x00\x19\x00\x1a\x00\x80\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xbb\x01\x7b\x01\x7c\x01\x86\x00\x87\x00\xe8\x00\xb4\x01\x1b\x00\x16\x00\x5b\x00\x6a\x00\x80\x00\x18\x00\x19\x00\x1a\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\xfe\x00\xff\x00\x00\x01\x11\x00\x89\x00\x01\x01\x1b\x00\x16\x00\x5b\x00\x5e\x00\xb7\x01\x18\x00\x19\x00\x1a\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\xb8\x01\x6b\x00\xdf\xff\xbe\x00\x87\x00\x80\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x78\x00\x18\x00\x19\x00\x79\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\xb0\xff\x6b\x00\xde\xff\xb0\xff\x11\x00\xbf\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x78\x00\x18\x00\x19\x00\x79\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\x2d\x01\x38\x01\xff\xff\x80\x00\xd6\x00\x10\x00\x1b\x00\x2e\x01\x5b\x00\x5e\x00\x15\x01\xed\xff\x11\x00\x4e\x01\x5c\x00\xa8\x01\x3a\x01\x04\x01\x05\x01\x5d\x00\xb9\x01\x6b\x00\xf2\x00\x80\x00\x16\x01\x17\x01\x16\x00\x3c\x00\x3d\x00\x5e\x00\x18\x00\x19\x00\x79\x00\x80\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x25\x01\xae\x01\xa9\x01\x6b\x00\xaa\x01\x98\x01\x99\x01\x1b\x00\x16\x00\x5b\x00\x27\x01\x70\x01\x18\x00\x19\x00\x79\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\xea\x00\xbf\x01\x11\x00\x12\x00\x71\x01\x3e\x00\x1b\x00\x93\x01\x5b\x00\x5e\x00\xa0\x00\x7f\x00\x25\x01\x26\x01\x5c\x00\x3c\x00\x3d\x00\x9f\x01\x10\x00\x5d\x00\xee\x00\x6b\x00\x27\x01\x30\x00\xef\x00\x31\x00\x16\x00\x17\x00\x80\x00\x5e\x00\x18\x00\x19\x00\x1a\x00\xd6\x00\x10\x00\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x95\x01\x6b\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x86\x01\x32\x00\xe6\x00\x11\x00\x12\x00\xf0\x00\x3e\x00\x33\x00\x44\x00\xf1\x00\xa1\x00\x1b\x00\xce\x00\x45\x00\xbb\x00\x3c\x00\x3d\x00\x08\x01\x96\x01\x46\x00\x38\x01\x09\x01\x35\x00\x24\x00\x47\x00\x3e\x01\x48\x00\x8a\x01\x34\x01\x49\x00\x97\x01\x8b\x01\x35\x01\x4a\x00\x39\x01\x3a\x01\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x4b\x00\x4c\x00\x18\x00\x19\x00\x1a\x00\xc6\x00\xc7\x00\xe6\x00\x11\x00\x12\x00\x80\x00\x3e\x00\x9e\x01\x43\x00\x44\x00\x11\x00\x12\x00\x1b\x00\x4d\x01\x45\x00\x6b\x01\x39\x00\x3a\x00\x3b\x00\x80\x00\x46\x00\xc4\x00\xc5\x00\x3c\x00\x3d\x00\x47\x00\x24\x00\x48\x00\xdc\x00\x50\x01\x49\x00\xc6\x00\xc7\x00\xc8\x00\x4a\x00\x53\x01\x10\x00\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x4b\x00\x4c\x00\x18\x00\x19\x00\x1a\x00\x68\x01\x10\x00\x16\x00\x21\x01\x10\x00\x22\x01\x18\x00\x19\x00\x1a\x00\x44\x00\x11\x00\x12\x00\x1b\x00\x3e\x00\x45\x00\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x46\x00\x1b\x00\x18\x00\x19\x00\x1a\x00\x47\x00\xe4\x00\x48\x00\xa2\x01\x29\x01\x49\x00\x4d\x01\x11\x00\x12\x00\x4a\x00\xd1\x00\xa7\x01\x1b\x00\xb5\x01\x45\x00\xcf\x00\xd0\x00\x4b\x00\x4c\x00\x52\x01\x46\x00\x11\x00\x12\x00\x5e\x01\xd1\x00\x47\x00\x55\x01\x48\x00\x16\x00\x17\x00\x49\x00\x16\x00\x18\x00\x19\x00\x1a\x00\x18\x00\x19\x00\x1a\x00\xd6\x00\x10\x00\x16\x00\x66\x01\x4b\x00\x4c\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x80\x00\x24\x00\x1b\x00\x25\x00\x5b\x00\x8f\x00\x67\x01\x1c\x00\x11\x00\x3b\x01\x8b\x00\x1b\x00\x96\x00\x5b\x00\xf6\x00\x5d\x00\x8e\x01\x16\x00\x70\x01\x8b\x00\x8c\x00\x18\x00\x19\x00\x1a\x00\x5d\x00\x5e\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x5e\x00\x74\x01\x1b\x00\x77\x01\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xb1\x00\x11\x00\x8f\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\xb2\x00\x0f\x00\x10\x00\x91\x01\x3c\x00\x3d\x00\x84\x01\xb7\x00\xdf\x00\xb3\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\xe0\x00\x2c\x00\xde\x00\x2d\x00\x3c\x00\x3d\x00\xed\x00\x11\x00\x12\x00\xb8\x00\x2e\x00\xfc\x00\xb9\x00\x21\x01\x10\x00\x23\x01\xc1\x00\xbb\x00\xbc\x00\xbd\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\xfd\x00\x3e\x00\x3c\x00\x3d\x00\x03\x01\xbb\x00\x0a\x01\x80\x01\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x14\x01\x3e\x00\x3c\x00\x3d\x00\xc3\x01\xd3\x00\x1d\x01\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x32\x01\xd1\x00\x3c\x00\x3d\x00\x21\x01\x10\x00\x24\x01\xa8\x00\xa9\x00\x11\x00\x12\x00\x1e\x01\x3e\x00\xc2\x00\x0f\x00\x10\x00\xb5\x01\xd6\x00\x10\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x33\x01\x3e\x00\x3c\x00\x3d\x00\xba\x01\xc9\x01\xca\x01\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x3b\x01\x3e\x00\x3c\x00\x3d\x00\xbd\x01\xe9\x00\xea\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3e\x01\xdb\x00\x0f\x00\x10\x00\x3c\x00\x3d\x00\x02\x01\xfd\x00\x2f\x01\x2c\x01\x31\x01\x2e\x01\x11\x00\x12\x00\x48\x01\x3e\x00\xff\xff\x7a\x00\x93\x01\x7b\x00\x7c\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\xff\xff\x3e\x00\x3c\x00\x3d\x00\x99\x01\x91\x00\x92\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x23\x00\x3e\x00\x3c\x00\x3d\x00\x9e\x01\x93\x00\x9d\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\xff\xff\xc1\x00\x80\x00\xd6\x00\x3c\x00\x3d\x00\xff\xff\xff\xff\x0e\x00\x43\x00\x00\x00\x00\x00\x11\x00\x12\x00\x4f\x00\x3e\x00\x62\x00\x00\x00\xa2\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x67\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x75\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x77\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x78\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x7d\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x7e\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x7f\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x82\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x1f\x01\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x5f\x00\x00\x00\x00\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x3c\x00\x3d\x00\x00\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x00\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x11\x00\x12\x00\x00\x00\x3e\x00\xce\x00\x12\x01\x00\x00\x00\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x35\x00\x18\x00\x19\x00\x1a\x00\x11\x00\x12\x00\x30\x00\x3e\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\xcd\x00\xa1\x00\x00\x00\x1b\x00\xce\x00\x32\x00\x3c\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\x34\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x32\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x00\x00\x33\x00\x00\x00\x00\x00\x16\x00\x1b\x00\xce\x00\x32\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\x34\x00\x31\x00\x16\x00\x17\x00\x00\x00\x1b\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x1b\x00\xce\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\xce\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x1b\x00\xce\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\x34\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x1b\x00\xce\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\xce\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x30\x00\x00\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\xd5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x1b\x00\xce\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x35\x00\x30\x00\xce\x00\x31\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x35\x00\x81\x01\x39\x00\x3a\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x1b\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x16\x00\x00\x00\x00\x00\x34\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x16\x00\x35\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x00\x00\x5b\x00\x11\x00\x12\x00\x00\x00\x3e\x00\x00\x00\x5c\x00\x00\x00\x16\x00\x00\x00\x1b\x00\x5d\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x00\x00\x5e\x00\x00\x00\x59\x01\x84\x00\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1b\x00\x00\x00\x5b\x00\x5e\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x5c\x00\x00\x00\x00\x00\x16\x00\x00\x00\x5d\x00\xa4\x01\x18\x00\x19\x00\x1a\x00\x00\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5e\x00\xbc\x01\x7c\x01\x86\x00\x87\x00\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\x5b\x01\x00\x00\x00\x00\x11\x00\x89\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x00\x00\x18\x00\x19\x00\x45\x01\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\x8c\x00\x86\x00\x87\x00\x8d\x00\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x5c\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5d\x00\x00\x00\x00\x00\x11\x00\x89\x00\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x5c\x00\x00\x00\x00\x00\x16\x00\x00\x00\x5d\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x8b\x00\x00\x00\x1b\x00\x00\x00\x00\x00\x5d\x00\x00\x00\x00\x00\x00\x00\xae\x01\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\xb1\x00\x18\x00\x19\x00\x1a\x00\x8b\x00\x5f\x01\x86\x00\x87\x00\x00\x00\x5d\x00\x60\x01\x86\x00\x87\x00\x07\x01\x00\x00\x00\x00\x1b\x00\x16\x00\x5b\x00\x5e\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x8b\x00\x8c\x00\x00\x00\x11\x00\x89\x00\x5d\x00\x00\x00\x00\x00\x11\x00\x89\x00\x00\x00\x00\x00\x1b\x00\x00\x00\x5b\x00\x5e\x00\x00\x00\x00\x00\x2b\xff\x00\x00\x8b\x00\x2b\xff\x2b\xff\x00\x00\x00\x00\x5d\x00\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x00\x00\x2b\xff\x2b\xff\x2b\xff\x5e\x00\x00\x00\x2b\xff\x40\x00\x41\x00\x42\x00\x16\x00\x17\x00\x2b\xff\x2b\xff\x18\x00\x19\x00\x1a\x00\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x2b\xff\x00\x00\x00\x00\x2b\xff\x1b\x00\x16\x00\x45\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x46\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x00\x00\x00\x48\x00\x00\x00\x16\x00\x49\x00\x00\x00\x1b\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x00\x00\x16\x00\x29\x01\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x1b\x00\xb0\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x01\x00\x00\x1b\x00\x8f\x01\xa6\x00\x00\x00\x00\x00\x16\x00\x17\x00\x65\x01\x29\x01\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x16\x00\x90\x01\x00\x00\x2a\x01\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x00\x00\x1b\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xa7\x00\x1b\x00\xe6\x00\x00\x00\x00\x00\xa8\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x16\x00\xca\x00\x00\x00\x16\x00\x18\x00\x19\x00\x1a\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x1b\x00\x16\x00\x27\x00\x1b\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x1b\x01\x27\xff\x00\x00\x3d\x01\x79\x01\x7a\x01\x7b\x01\x7c\x01\x86\x00\x87\x00\x27\xff\x27\xff\x1b\x00\xeb\x00\xec\x00\x27\xff\x27\xff\x27\xff\x27\xff\x27\xff\x27\xff\x27\xff\x27\xff\x27\xff\x6d\x01\x00\x00\x27\xff\x00\x00\x00\x00\x11\x00\x89\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xec\x00\x00\x00\x00\x00\x00\x00\x72\x01\x00\x00\x00\x00\x00\x00\x00\x00\x16\x00\x17\x00\x00\x00\x00\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xc0\x01\x28\x00\x29\x00\x00\x00\x1b\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\xa5\x01\x28\x00\x29\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x00\x00\x2a\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x17\x01\x28\x00\x29\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x00\x00\x2a\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x27\x00\x28\x00\x29\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x00\x00\x2a\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x16\x00\x27\x00\x00\x00\xd9\x00\x18\x00\x19\x00\x1a\x00\x00\x00\x00\x00\xda\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x87\x01\x11\x00\x12\x00\x1b\x00\x2e\x00\x88\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x0c\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x0d\x01\x00\x00\x00\x00\x0e\x01\x12\x00\xc4\x00\x2e\x00\x00\x00\x00\x00\x0f\x01\x10\x01\x00\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\xd8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\xca\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\xcb\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x88\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x9a\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xa0\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x5e\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x61\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x8b\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x8c\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xdf\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xe1\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xe2\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xe3\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xf1\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x12\x01\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xce\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\xd8\x00\x2b\x00\x2c\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x11\x00\x12\x00\x00\x00\x2e\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
happyReduceArr = Happy_Data_Array.array (12, 250) [
(12 , happyReduce_12),
(13 , happyReduce_13),
(14 , happyReduce_14),
(15 , happyReduce_15),
(16 , happyReduce_16),
(17 , happyReduce_17),
(18 , happyReduce_18),
(19 , happyReduce_19),
(20 , happyReduce_20),
(21 , happyReduce_21),
(22 , happyReduce_22),
(23 , happyReduce_23),
(24 , happyReduce_24),
(25 , happyReduce_25),
(26 , happyReduce_26),
(27 , happyReduce_27),
(28 , happyReduce_28),
(29 , happyReduce_29),
(30 , happyReduce_30),
(31 , happyReduce_31),
(32 , happyReduce_32),
(33 , happyReduce_33),
(34 , happyReduce_34),
(35 , happyReduce_35),
(36 , happyReduce_36),
(37 , happyReduce_37),
(38 , happyReduce_38),
(39 , happyReduce_39),
(40 , happyReduce_40),
(41 , happyReduce_41),
(42 , happyReduce_42),
(43 , happyReduce_43),
(44 , happyReduce_44),
(45 , happyReduce_45),
(46 , happyReduce_46),
(47 , happyReduce_47),
(48 , happyReduce_48),
(49 , happyReduce_49),
(50 , happyReduce_50),
(51 , happyReduce_51),
(52 , happyReduce_52),
(53 , happyReduce_53),
(54 , happyReduce_54),
(55 , happyReduce_55),
(56 , happyReduce_56),
(57 , happyReduce_57),
(58 , happyReduce_58),
(59 , happyReduce_59),
(60 , happyReduce_60),
(61 , happyReduce_61),
(62 , happyReduce_62),
(63 , happyReduce_63),
(64 , happyReduce_64),
(65 , happyReduce_65),
(66 , happyReduce_66),
(67 , happyReduce_67),
(68 , happyReduce_68),
(69 , happyReduce_69),
(70 , happyReduce_70),
(71 , happyReduce_71),
(72 , happyReduce_72),
(73 , happyReduce_73),
(74 , happyReduce_74),
(75 , happyReduce_75),
(76 , happyReduce_76),
(77 , happyReduce_77),
(78 , happyReduce_78),
(79 , happyReduce_79),
(80 , happyReduce_80),
(81 , happyReduce_81),
(82 , happyReduce_82),
(83 , happyReduce_83),
(84 , happyReduce_84),
(85 , happyReduce_85),
(86 , happyReduce_86),
(87 , happyReduce_87),
(88 , happyReduce_88),
(89 , happyReduce_89),
(90 , happyReduce_90),
(91 , happyReduce_91),
(92 , happyReduce_92),
(93 , happyReduce_93),
(94 , happyReduce_94),
(95 , happyReduce_95),
(96 , happyReduce_96),
(97 , happyReduce_97),
(98 , happyReduce_98),
(99 , happyReduce_99),
(100 , happyReduce_100),
(101 , happyReduce_101),
(102 , happyReduce_102),
(103 , happyReduce_103),
(104 , happyReduce_104),
(105 , happyReduce_105),
(106 , happyReduce_106),
(107 , happyReduce_107),
(108 , happyReduce_108),
(109 , happyReduce_109),
(110 , happyReduce_110),
(111 , happyReduce_111),
(112 , happyReduce_112),
(113 , happyReduce_113),
(114 , happyReduce_114),
(115 , happyReduce_115),
(116 , happyReduce_116),
(117 , happyReduce_117),
(118 , happyReduce_118),
(119 , happyReduce_119),
(120 , happyReduce_120),
(121 , happyReduce_121),
(122 , happyReduce_122),
(123 , happyReduce_123),
(124 , happyReduce_124),
(125 , happyReduce_125),
(126 , happyReduce_126),
(127 , happyReduce_127),
(128 , happyReduce_128),
(129 , happyReduce_129),
(130 , happyReduce_130),
(131 , happyReduce_131),
(132 , happyReduce_132),
(133 , happyReduce_133),
(134 , happyReduce_134),
(135 , happyReduce_135),
(136 , happyReduce_136),
(137 , happyReduce_137),
(138 , happyReduce_138),
(139 , happyReduce_139),
(140 , happyReduce_140),
(141 , happyReduce_141),
(142 , happyReduce_142),
(143 , happyReduce_143),
(144 , happyReduce_144),
(145 , happyReduce_145),
(146 , happyReduce_146),
(147 , happyReduce_147),
(148 , happyReduce_148),
(149 , happyReduce_149),
(150 , happyReduce_150),
(151 , happyReduce_151),
(152 , happyReduce_152),
(153 , happyReduce_153),
(154 , happyReduce_154),
(155 , happyReduce_155),
(156 , happyReduce_156),
(157 , happyReduce_157),
(158 , happyReduce_158),
(159 , happyReduce_159),
(160 , happyReduce_160),
(161 , happyReduce_161),
(162 , happyReduce_162),
(163 , happyReduce_163),
(164 , happyReduce_164),
(165 , happyReduce_165),
(166 , happyReduce_166),
(167 , happyReduce_167),
(168 , happyReduce_168),
(169 , happyReduce_169),
(170 , happyReduce_170),
(171 , happyReduce_171),
(172 , happyReduce_172),
(173 , happyReduce_173),
(174 , happyReduce_174),
(175 , happyReduce_175),
(176 , happyReduce_176),
(177 , happyReduce_177),
(178 , happyReduce_178),
(179 , happyReduce_179),
(180 , happyReduce_180),
(181 , happyReduce_181),
(182 , happyReduce_182),
(183 , happyReduce_183),
(184 , happyReduce_184),
(185 , happyReduce_185),
(186 , happyReduce_186),
(187 , happyReduce_187),
(188 , happyReduce_188),
(189 , happyReduce_189),
(190 , happyReduce_190),
(191 , happyReduce_191),
(192 , happyReduce_192),
(193 , happyReduce_193),
(194 , happyReduce_194),
(195 , happyReduce_195),
(196 , happyReduce_196),
(197 , happyReduce_197),
(198 , happyReduce_198),
(199 , happyReduce_199),
(200 , happyReduce_200),
(201 , happyReduce_201),
(202 , happyReduce_202),
(203 , happyReduce_203),
(204 , happyReduce_204),
(205 , happyReduce_205),
(206 , happyReduce_206),
(207 , happyReduce_207),
(208 , happyReduce_208),
(209 , happyReduce_209),
(210 , happyReduce_210),
(211 , happyReduce_211),
(212 , happyReduce_212),
(213 , happyReduce_213),
(214 , happyReduce_214),
(215 , happyReduce_215),
(216 , happyReduce_216),
(217 , happyReduce_217),
(218 , happyReduce_218),
(219 , happyReduce_219),
(220 , happyReduce_220),
(221 , happyReduce_221),
(222 , happyReduce_222),
(223 , happyReduce_223),
(224 , happyReduce_224),
(225 , happyReduce_225),
(226 , happyReduce_226),
(227 , happyReduce_227),
(228 , happyReduce_228),
(229 , happyReduce_229),
(230 , happyReduce_230),
(231 , happyReduce_231),
(232 , happyReduce_232),
(233 , happyReduce_233),
(234 , happyReduce_234),
(235 , happyReduce_235),
(236 , happyReduce_236),
(237 , happyReduce_237),
(238 , happyReduce_238),
(239 , happyReduce_239),
(240 , happyReduce_240),
(241 , happyReduce_241),
(242 , happyReduce_242),
(243 , happyReduce_243),
(244 , happyReduce_244),
(245 , happyReduce_245),
(246 , happyReduce_246),
(247 , happyReduce_247),
(248 , happyReduce_248),
(249 , happyReduce_249),
(250 , happyReduce_250)
]
happy_n_terms = 60 :: Int
happy_n_nonterms = 83 :: Int
happyReduce_12 = happyReduce 6# 0# happyReduction_12
happyReduction_12 (happy_x_6 `HappyStk`
happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut92 happy_x_2 of { happy_var_2 ->
case happyOut16 happy_x_5 of { happy_var_5 ->
happyIn15
(let (is,ts) = happy_var_5 in Module happy_var_2 is ts
) `HappyStk` happyRest}}
happyReduce_13 = happySpecReduce_3 0# happyReduction_13
happyReduction_13 happy_x_3
happy_x_2
happy_x_1
= case happyOut16 happy_x_2 of { happy_var_2 ->
happyIn15
(let { (is,ts) = happy_var_2
-- XXX make a location from is and ts
; modName = Located { srcRange = emptyRange
, thing = mkModName ["Main"]
}
} in Module modName is ts
)}
happyReduce_14 = happySpecReduce_3 1# happyReduction_14
happyReduction_14 happy_x_3
happy_x_2
happy_x_1
= case happyOut17 happy_x_1 of { happy_var_1 ->
case happyOut26 happy_x_3 of { happy_var_3 ->
happyIn16
((reverse happy_var_1, reverse happy_var_3)
)}}
happyReduce_15 = happySpecReduce_3 1# happyReduction_15
happyReduction_15 happy_x_3
happy_x_2
happy_x_1
= case happyOut17 happy_x_1 of { happy_var_1 ->
case happyOut26 happy_x_3 of { happy_var_3 ->
happyIn16
((reverse happy_var_1, reverse happy_var_3)
)}}
happyReduce_16 = happySpecReduce_1 1# happyReduction_16
happyReduction_16 happy_x_1
= case happyOut17 happy_x_1 of { happy_var_1 ->
happyIn16
((reverse happy_var_1, [])
)}
happyReduce_17 = happySpecReduce_1 1# happyReduction_17
happyReduction_17 happy_x_1
= case happyOut26 happy_x_1 of { happy_var_1 ->
happyIn16
(([], reverse happy_var_1)
)}
happyReduce_18 = happySpecReduce_0 1# happyReduction_18
happyReduction_18 = happyIn16
(([], [])
)
happyReduce_19 = happySpecReduce_3 2# happyReduction_19
happyReduction_19 happy_x_3
happy_x_2
happy_x_1
= case happyOut17 happy_x_1 of { happy_var_1 ->
case happyOut18 happy_x_3 of { happy_var_3 ->
happyIn17
(happy_var_3 : happy_var_1
)}}
happyReduce_20 = happySpecReduce_3 2# happyReduction_20
happyReduction_20 happy_x_3
happy_x_2
happy_x_1
= case happyOut17 happy_x_1 of { happy_var_1 ->
case happyOut18 happy_x_3 of { happy_var_3 ->
happyIn17
(happy_var_3 : happy_var_1
)}}
happyReduce_21 = happySpecReduce_1 2# happyReduction_21
happyReduction_21 happy_x_1
= case happyOut18 happy_x_1 of { happy_var_1 ->
happyIn17
([happy_var_1]
)}
happyReduce_22 = happyReduce 4# 3# happyReduction_22
happyReduction_22 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_import) _)) ->
case happyOut92 happy_x_2 of { happy_var_2 ->
case happyOut19 happy_x_3 of { happy_var_3 ->
case happyOut20 happy_x_4 of { happy_var_4 ->
happyIn18
(Located { srcRange = rComb happy_var_1
$ fromMaybe (srcRange happy_var_2)
$ msum [ fmap srcRange happy_var_4
, fmap srcRange happy_var_3
]
, thing = Import
{ iModule = thing happy_var_2
, iAs = fmap thing happy_var_3
, iSpec = fmap thing happy_var_4
}
}
) `HappyStk` happyRest}}}}
happyReduce_23 = happySpecReduce_2 4# happyReduction_23
happyReduction_23 happy_x_2
happy_x_1
= case happyOut92 happy_x_2 of { happy_var_2 ->
happyIn19
(Just happy_var_2
)}
happyReduce_24 = happySpecReduce_0 4# happyReduction_24
happyReduction_24 = happyIn19
(Nothing
)
happyReduce_25 = happyReduce 4# 5# happyReduction_25
happyReduction_25 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut22 happy_x_1 of { happy_var_1 ->
case happyOut21 happy_x_3 of { happy_var_3 ->
happyIn20
(Just Located
{ srcRange = case happy_var_3 of
{ [] -> emptyRange
; xs -> rCombs (map srcRange xs) }
, thing = happy_var_1 (reverse (map thing happy_var_3))
}
) `HappyStk` happyRest}}
happyReduce_26 = happySpecReduce_0 5# happyReduction_26
happyReduction_26 = happyIn20
(Nothing
)
happyReduce_27 = happySpecReduce_3 6# happyReduction_27
happyReduction_27 happy_x_3
happy_x_2
happy_x_1
= case happyOut21 happy_x_1 of { happy_var_1 ->
case happyOut90 happy_x_3 of { happy_var_3 ->
happyIn21
(happy_var_3 : happy_var_1
)}}
happyReduce_28 = happySpecReduce_1 6# happyReduction_28
happyReduction_28 happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
happyIn21
([happy_var_1]
)}
happyReduce_29 = happySpecReduce_0 6# happyReduction_29
happyReduction_29 = happyIn21
([]
)
happyReduce_30 = happySpecReduce_1 7# happyReduction_30
happyReduction_30 happy_x_1
= happyIn22
(Hiding
)
happyReduce_31 = happySpecReduce_0 7# happyReduction_31
happyReduction_31 = happyIn22
(Only
)
happyReduce_32 = happySpecReduce_1 8# happyReduction_32
happyReduction_32 happy_x_1
= case happyOut25 happy_x_1 of { happy_var_1 ->
happyIn23
(Program (reverse happy_var_1)
)}
happyReduce_33 = happySpecReduce_0 8# happyReduction_33
happyReduction_33 = happyIn23
(Program []
)
happyReduce_34 = happySpecReduce_3 9# happyReduction_34
happyReduction_34 happy_x_3
happy_x_2
happy_x_1
= case happyOut26 happy_x_2 of { happy_var_2 ->
happyIn24
(Program (reverse happy_var_2)
)}
happyReduce_35 = happySpecReduce_2 9# happyReduction_35
happyReduction_35 happy_x_2
happy_x_1
= happyIn24
(Program []
)
happyReduce_36 = happySpecReduce_2 10# happyReduction_36
happyReduction_36 happy_x_2
happy_x_1
= case happyOut28 happy_x_1 of { happy_var_1 ->
happyIn25
(happy_var_1
)}
happyReduce_37 = happySpecReduce_3 10# happyReduction_37
happyReduction_37 happy_x_3
happy_x_2
happy_x_1
= case happyOut25 happy_x_1 of { happy_var_1 ->
case happyOut28 happy_x_2 of { happy_var_2 ->
happyIn25
(happy_var_2 ++ happy_var_1
)}}
happyReduce_38 = happySpecReduce_1 11# happyReduction_38
happyReduction_38 happy_x_1
= case happyOut27 happy_x_1 of { happy_var_1 ->
happyIn26
(happy_var_1
)}
happyReduce_39 = happySpecReduce_3 11# happyReduction_39
happyReduction_39 happy_x_3
happy_x_2
happy_x_1
= case happyOut26 happy_x_1 of { happy_var_1 ->
case happyOut27 happy_x_3 of { happy_var_3 ->
happyIn26
(happy_var_3 ++ happy_var_1
)}}
happyReduce_40 = happySpecReduce_3 11# happyReduction_40
happyReduction_40 happy_x_3
happy_x_2
happy_x_1
= case happyOut26 happy_x_1 of { happy_var_1 ->
case happyOut27 happy_x_3 of { happy_var_3 ->
happyIn26
(happy_var_3 ++ happy_var_1
)}}
happyReduce_41 = happySpecReduce_1 12# happyReduction_41
happyReduction_41 happy_x_1
= case happyOut33 happy_x_1 of { happy_var_1 ->
happyIn27
([exportDecl Nothing Public happy_var_1]
)}
happyReduce_42 = happySpecReduce_2 12# happyReduction_42
happyReduction_42 happy_x_2
happy_x_1
= case happyOut31 happy_x_1 of { happy_var_1 ->
case happyOut33 happy_x_2 of { happy_var_2 ->
happyIn27
([exportDecl (Just happy_var_1) Public happy_var_2]
)}}
happyReduce_43 = happyMonadReduce 3# 12# happyReduction_43
happyReduction_43 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_3 of { (happy_var_3@(Located _ (Token (StrLit {}) _))) ->
( (return . Include) `fmap` fromStrLit happy_var_3)}
) (\r -> happyReturn (happyIn27 r))
happyReduce_44 = happyReduce 6# 12# happyReduction_44
happyReduction_44 (happy_x_6 `HappyStk`
happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut32 happy_x_1 of { happy_var_1 ->
case happyOut91 happy_x_3 of { happy_var_3 ->
case happyOut39 happy_x_4 of { happy_var_4 ->
case happyOut45 happy_x_6 of { happy_var_6 ->
happyIn27
([exportDecl happy_var_1 Public (mkProperty happy_var_3 happy_var_4 happy_var_6)]
) `HappyStk` happyRest}}}}
happyReduce_45 = happyReduce 5# 12# happyReduction_45
happyReduction_45 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut32 happy_x_1 of { happy_var_1 ->
case happyOut91 happy_x_3 of { happy_var_3 ->
case happyOut45 happy_x_5 of { happy_var_5 ->
happyIn27
([exportDecl happy_var_1 Public (mkProperty happy_var_3 [] happy_var_5)]
) `HappyStk` happyRest}}}
happyReduce_46 = happySpecReduce_2 12# happyReduction_46
happyReduction_46 happy_x_2
happy_x_1
= case happyOut35 happy_x_2 of { happy_var_2 ->
happyIn27
([exportNewtype Public happy_var_2]
)}
happyReduce_47 = happySpecReduce_1 12# happyReduction_47
happyReduction_47 happy_x_1
= case happyOut30 happy_x_1 of { happy_var_1 ->
happyIn27
(happy_var_1
)}
happyReduce_48 = happySpecReduce_1 12# happyReduction_48
happyReduction_48 happy_x_1
= case happyOut29 happy_x_1 of { happy_var_1 ->
happyIn27
(happy_var_1
)}
happyReduce_49 = happySpecReduce_1 13# happyReduction_49
happyReduction_49 happy_x_1
= case happyOut33 happy_x_1 of { happy_var_1 ->
happyIn28
([Decl (TopLevel {tlExport = Public, tlValue = happy_var_1 })]
)}
happyReduce_50 = happyMonadReduce 2# 13# happyReduction_50
happyReduction_50 (happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_2 of { (happy_var_2@(Located _ (Token (StrLit {}) _))) ->
( (return . Include) `fmap` fromStrLit happy_var_2)}
) (\r -> happyReturn (happyIn28 r))
happyReduce_51 = happySpecReduce_1 13# happyReduction_51
happyReduction_51 happy_x_1
= case happyOut30 happy_x_1 of { happy_var_1 ->
happyIn28
(happy_var_1
)}
happyReduce_52 = happyReduce 4# 14# happyReduction_52
happyReduction_52 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut26 happy_x_3 of { happy_var_3 ->
happyIn29
(changeExport Private (reverse happy_var_3)
) `HappyStk` happyRest}
happyReduce_53 = happyReduce 5# 14# happyReduction_53
happyReduction_53 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut26 happy_x_4 of { happy_var_4 ->
happyIn29
(changeExport Private (reverse happy_var_4)
) `HappyStk` happyRest}
happyReduce_54 = happyReduce 5# 15# happyReduction_54
happyReduction_54 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut32 happy_x_1 of { happy_var_1 ->
case happyOut91 happy_x_3 of { happy_var_3 ->
case happyOut74 happy_x_5 of { happy_var_5 ->
happyIn30
(mkPrimDecl happy_var_1 happy_var_3 happy_var_5
) `HappyStk` happyRest}}}
happyReduce_55 = happyReduce 7# 15# happyReduction_55
happyReduction_55 (happy_x_7 `HappyStk`
happy_x_6 `HappyStk`
happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut32 happy_x_1 of { happy_var_1 ->
case happyOut53 happy_x_4 of { happy_var_4 ->
case happyOut74 happy_x_7 of { happy_var_7 ->
happyIn30
(mkPrimDecl happy_var_1 happy_var_4 happy_var_7
) `HappyStk` happyRest}}}
happyReduce_56 = happySpecReduce_1 16# happyReduction_56
happyReduction_56 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (White DocStr) _))) ->
happyIn31
(mkDoc (fmap tokenText happy_var_1)
)}
happyReduce_57 = happySpecReduce_1 17# happyReduction_57
happyReduction_57 happy_x_1
= case happyOut31 happy_x_1 of { happy_var_1 ->
happyIn32
(Just happy_var_1
)}
happyReduce_58 = happySpecReduce_0 17# happyReduction_58
happyReduction_58 = happyIn32
(Nothing
)
happyReduce_59 = happySpecReduce_3 18# happyReduction_59
happyReduction_59 happy_x_3
happy_x_2
happy_x_1
= case happyOut37 happy_x_1 of { happy_var_1 ->
case happyOut74 happy_x_3 of { happy_var_3 ->
happyIn33
(at (head happy_var_1,happy_var_3) $ DSignature (reverse happy_var_1) happy_var_3
)}}
happyReduce_60 = happySpecReduce_3 18# happyReduction_60
happyReduction_60 happy_x_3
happy_x_2
happy_x_1
= case happyOut69 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn33
(at (happy_var_1,happy_var_3) $ DPatBind happy_var_1 happy_var_3
)}}
happyReduce_61 = happyReduce 5# 18# happyReduction_61
happyReduction_61 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut53 happy_x_2 of { happy_var_2 ->
case happyOut45 happy_x_5 of { happy_var_5 ->
happyIn33
(at (happy_var_1,happy_var_5) $ DPatBind (PVar happy_var_2) happy_var_5
) `HappyStk` happyRest}}}
happyReduce_62 = happyReduce 4# 18# happyReduction_62
happyReduction_62 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut38 happy_x_1 of { happy_var_1 ->
case happyOut39 happy_x_2 of { happy_var_2 ->
case happyOut45 happy_x_4 of { happy_var_4 ->
happyIn33
(at (happy_var_1,happy_var_4) $
DBind $ Bind { bName = happy_var_1
, bParams = reverse happy_var_2
, bDef = at happy_var_4 (Located emptyRange (DExpr happy_var_4))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
}
) `HappyStk` happyRest}}}
happyReduce_63 = happyReduce 5# 18# happyReduction_63
happyReduction_63 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut70 happy_x_1 of { happy_var_1 ->
case happyOut54 happy_x_2 of { happy_var_2 ->
case happyOut70 happy_x_3 of { happy_var_3 ->
case happyOut45 happy_x_5 of { happy_var_5 ->
happyIn33
(at (happy_var_1,happy_var_5) $
DBind $ Bind { bName = happy_var_2
, bParams = [happy_var_1,happy_var_3]
, bDef = at happy_var_5 (Located emptyRange (DExpr happy_var_5))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = True
, bFixity = Nothing
, bDoc = Nothing
}
) `HappyStk` happyRest}}}}
happyReduce_64 = happyMonadReduce 4# 18# happyReduction_64
happyReduction_64 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_type ) _)) ->
case happyOut91 happy_x_2 of { happy_var_2 ->
case happyOut82 happy_x_4 of { happy_var_4 ->
( at (happy_var_1,happy_var_4) `fmap` mkTySyn happy_var_2 [] happy_var_4)}}}
) (\r -> happyReturn (happyIn33 r))
happyReduce_65 = happyMonadReduce 5# 18# happyReduction_65
happyReduction_65 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_type ) _)) ->
case happyOut91 happy_x_2 of { happy_var_2 ->
case happyOut81 happy_x_3 of { happy_var_3 ->
case happyOut82 happy_x_5 of { happy_var_5 ->
( at (happy_var_1,happy_var_5) `fmap` mkTySyn happy_var_2 (reverse happy_var_3) happy_var_5)}}}}
) (\r -> happyReturn (happyIn33 r))
happyReduce_66 = happyMonadReduce 3# 18# happyReduction_66
happyReduction_66 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_2 of { (happy_var_2@(Located _ (Token (Num {}) _))) ->
case happyOut55 happy_x_3 of { happy_var_3 ->
( mkFixity LeftAssoc happy_var_2 (reverse happy_var_3))}}
) (\r -> happyReturn (happyIn33 r))
happyReduce_67 = happyMonadReduce 3# 18# happyReduction_67
happyReduction_67 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_2 of { (happy_var_2@(Located _ (Token (Num {}) _))) ->
case happyOut55 happy_x_3 of { happy_var_3 ->
( mkFixity RightAssoc happy_var_2 (reverse happy_var_3))}}
) (\r -> happyReturn (happyIn33 r))
happyReduce_68 = happyMonadReduce 3# 18# happyReduction_68
happyReduction_68 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_2 of { (happy_var_2@(Located _ (Token (Num {}) _))) ->
case happyOut55 happy_x_3 of { happy_var_3 ->
( mkFixity NonAssoc happy_var_2 (reverse happy_var_3))}}
) (\r -> happyReturn (happyIn33 r))
happyReduce_69 = happyReduce 4# 19# happyReduction_69
happyReduction_69 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut69 happy_x_2 of { happy_var_2 ->
case happyOut45 happy_x_4 of { happy_var_4 ->
happyIn34
(at (happy_var_2,happy_var_4) $ DPatBind happy_var_2 happy_var_4
) `HappyStk` happyRest}}
happyReduce_70 = happyReduce 5# 19# happyReduction_70
happyReduction_70 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut91 happy_x_2 of { happy_var_2 ->
case happyOut39 happy_x_3 of { happy_var_3 ->
case happyOut45 happy_x_5 of { happy_var_5 ->
happyIn34
(at (happy_var_2,happy_var_5) $
DBind $ Bind { bName = happy_var_2
, bParams = reverse happy_var_3
, bDef = at happy_var_5 (Located emptyRange (DExpr happy_var_5))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
}
) `HappyStk` happyRest}}}
happyReduce_71 = happyReduce 4# 20# happyReduction_71
happyReduction_71 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut93 happy_x_2 of { happy_var_2 ->
case happyOut36 happy_x_4 of { happy_var_4 ->
happyIn35
(Newtype { nName = happy_var_2, nParams = [], nBody = happy_var_4 }
) `HappyStk` happyRest}}
happyReduce_72 = happyReduce 5# 20# happyReduction_72
happyReduction_72 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut93 happy_x_2 of { happy_var_2 ->
case happyOut81 happy_x_3 of { happy_var_3 ->
case happyOut36 happy_x_5 of { happy_var_5 ->
happyIn35
(Newtype { nName = happy_var_2, nParams = happy_var_3, nBody = happy_var_5 }
) `HappyStk` happyRest}}}
happyReduce_73 = happySpecReduce_2 21# happyReduction_73
happyReduction_73 happy_x_2
happy_x_1
= happyIn36
([]
)
happyReduce_74 = happySpecReduce_3 21# happyReduction_74
happyReduction_74 happy_x_3
happy_x_2
happy_x_1
= case happyOut89 happy_x_2 of { happy_var_2 ->
happyIn36
(happy_var_2
)}
happyReduce_75 = happySpecReduce_1 22# happyReduction_75
happyReduction_75 happy_x_1
= case happyOut38 happy_x_1 of { happy_var_1 ->
happyIn37
([ happy_var_1]
)}
happyReduce_76 = happySpecReduce_3 22# happyReduction_76
happyReduction_76 happy_x_3
happy_x_2
happy_x_1
= case happyOut37 happy_x_1 of { happy_var_1 ->
case happyOut38 happy_x_3 of { happy_var_3 ->
happyIn37
(happy_var_3 : happy_var_1
)}}
happyReduce_77 = happySpecReduce_1 23# happyReduction_77
happyReduction_77 happy_x_1
= case happyOut91 happy_x_1 of { happy_var_1 ->
happyIn38
(happy_var_1
)}
happyReduce_78 = happySpecReduce_3 23# happyReduction_78
happyReduction_78 happy_x_3
happy_x_2
happy_x_1
= case happyOut53 happy_x_2 of { happy_var_2 ->
happyIn38
(happy_var_2
)}
happyReduce_79 = happySpecReduce_1 24# happyReduction_79
happyReduction_79 happy_x_1
= case happyOut70 happy_x_1 of { happy_var_1 ->
happyIn39
([happy_var_1]
)}
happyReduce_80 = happySpecReduce_2 24# happyReduction_80
happyReduction_80 happy_x_2
happy_x_1
= case happyOut40 happy_x_1 of { happy_var_1 ->
case happyOut70 happy_x_2 of { happy_var_2 ->
happyIn39
(happy_var_2 : happy_var_1
)}}
happyReduce_81 = happySpecReduce_1 25# happyReduction_81
happyReduction_81 happy_x_1
= case happyOut70 happy_x_1 of { happy_var_1 ->
happyIn40
([happy_var_1]
)}
happyReduce_82 = happySpecReduce_2 25# happyReduction_82
happyReduction_82 happy_x_2
happy_x_1
= case happyOut40 happy_x_1 of { happy_var_1 ->
case happyOut70 happy_x_2 of { happy_var_2 ->
happyIn40
(happy_var_2 : happy_var_1
)}}
happyReduce_83 = happySpecReduce_2 26# happyReduction_83
happyReduction_83 happy_x_2
happy_x_1
= case happyOut33 happy_x_1 of { happy_var_1 ->
happyIn41
([happy_var_1]
)}
happyReduce_84 = happySpecReduce_3 26# happyReduction_84
happyReduction_84 happy_x_3
happy_x_2
happy_x_1
= case happyOut41 happy_x_1 of { happy_var_1 ->
case happyOut33 happy_x_2 of { happy_var_2 ->
happyIn41
(happy_var_2 : happy_var_1
)}}
happyReduce_85 = happySpecReduce_1 27# happyReduction_85
happyReduction_85 happy_x_1
= case happyOut33 happy_x_1 of { happy_var_1 ->
happyIn42
([happy_var_1]
)}
happyReduce_86 = happySpecReduce_3 27# happyReduction_86
happyReduction_86 happy_x_3
happy_x_2
happy_x_1
= case happyOut42 happy_x_1 of { happy_var_1 ->
case happyOut33 happy_x_3 of { happy_var_3 ->
happyIn42
(happy_var_3 : happy_var_1
)}}
happyReduce_87 = happySpecReduce_3 27# happyReduction_87
happyReduction_87 happy_x_3
happy_x_2
happy_x_1
= case happyOut42 happy_x_1 of { happy_var_1 ->
case happyOut33 happy_x_3 of { happy_var_3 ->
happyIn42
(happy_var_3 : happy_var_1
)}}
happyReduce_88 = happySpecReduce_3 28# happyReduction_88
happyReduction_88 happy_x_3
happy_x_2
happy_x_1
= case happyOut42 happy_x_2 of { happy_var_2 ->
happyIn43
(happy_var_2
)}
happyReduce_89 = happySpecReduce_2 28# happyReduction_89
happyReduction_89 happy_x_2
happy_x_1
= happyIn43
([]
)
happyReduce_90 = happySpecReduce_1 29# happyReduction_90
happyReduction_90 happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
happyIn44
(ExprInput happy_var_1
)}
happyReduce_91 = happySpecReduce_1 29# happyReduction_91
happyReduction_91 happy_x_1
= case happyOut34 happy_x_1 of { happy_var_1 ->
happyIn44
(LetInput happy_var_1
)}
happyReduce_92 = happySpecReduce_1 30# happyReduction_92
happyReduction_92 happy_x_1
= case happyOut48 happy_x_1 of { happy_var_1 ->
happyIn45
(happy_var_1
)}
happyReduce_93 = happyReduce 4# 30# happyReduction_93
happyReduction_93 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOutTok happy_x_4 of { (Located happy_var_4 (Token (Sym CurlyR ) _)) ->
happyIn45
(at (happy_var_1,happy_var_4) $ EWhere happy_var_1 []
) `HappyStk` happyRest}}
happyReduce_94 = happyReduce 5# 30# happyReduction_94
happyReduction_94 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut41 happy_x_4 of { happy_var_4 ->
case happyOutTok happy_x_5 of { (Located happy_var_5 (Token (Sym CurlyR ) _)) ->
happyIn45
(at (happy_var_1,happy_var_5) $ EWhere happy_var_1 (reverse happy_var_4)
) `HappyStk` happyRest}}}
happyReduce_95 = happyReduce 4# 30# happyReduction_95
happyReduction_95 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (KW KW_where ) _)) ->
happyIn45
(at (happy_var_1,happy_var_2) $ EWhere happy_var_1 []
) `HappyStk` happyRest}}
happyReduce_96 = happyReduce 5# 30# happyReduction_96
happyReduction_96 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut42 happy_x_4 of { happy_var_4 ->
happyIn45
(at (happy_var_1,happy_var_4) $ EWhere happy_var_1 (reverse happy_var_4)
) `HappyStk` happyRest}}
happyReduce_97 = happySpecReduce_1 31# happyReduction_97
happyReduction_97 happy_x_1
= case happyOut47 happy_x_1 of { happy_var_1 ->
happyIn46
([happy_var_1]
)}
happyReduce_98 = happySpecReduce_3 31# happyReduction_98
happyReduction_98 happy_x_3
happy_x_2
happy_x_1
= case happyOut46 happy_x_1 of { happy_var_1 ->
case happyOut47 happy_x_3 of { happy_var_3 ->
happyIn46
(happy_var_3 : happy_var_1
)}}
happyReduce_99 = happySpecReduce_3 32# happyReduction_99
happyReduction_99 happy_x_3
happy_x_2
happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn47
((happy_var_1, happy_var_3)
)}}
happyReduce_100 = happySpecReduce_1 33# happyReduction_100
happyReduction_100 happy_x_1
= case happyOut49 happy_x_1 of { happy_var_1 ->
happyIn48
(happy_var_1
)}
happyReduce_101 = happyReduce 4# 33# happyReduction_101
happyReduction_101 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_if ) _)) ->
case happyOut46 happy_x_2 of { happy_var_2 ->
case happyOut48 happy_x_4 of { happy_var_4 ->
happyIn48
(at (happy_var_1,happy_var_4) $ mkIf (reverse happy_var_2) happy_var_4
) `HappyStk` happyRest}}}
happyReduce_102 = happyReduce 4# 33# happyReduction_102
happyReduction_102 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym Lambda ) _)) ->
case happyOut39 happy_x_2 of { happy_var_2 ->
case happyOut48 happy_x_4 of { happy_var_4 ->
happyIn48
(at (happy_var_1,happy_var_4) $ EFun (reverse happy_var_2) happy_var_4
) `HappyStk` happyRest}}}
happyReduce_103 = happySpecReduce_1 34# happyReduction_103
happyReduction_103 happy_x_1
= case happyOut50 happy_x_1 of { happy_var_1 ->
happyIn49
(happy_var_1
)}
happyReduce_104 = happySpecReduce_3 34# happyReduction_104
happyReduction_104 happy_x_3
happy_x_2
happy_x_1
= case happyOut50 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn49
(at (happy_var_1,happy_var_3) $ ETyped happy_var_1 happy_var_3
)}}
happyReduce_105 = happySpecReduce_1 35# happyReduction_105
happyReduction_105 happy_x_1
= case happyOut51 happy_x_1 of { happy_var_1 ->
happyIn50
(happy_var_1
)}
happyReduce_106 = happySpecReduce_3 35# happyReduction_106
happyReduction_106 happy_x_3
happy_x_2
happy_x_1
= case happyOut50 happy_x_1 of { happy_var_1 ->
case happyOut52 happy_x_2 of { happy_var_2 ->
case happyOut51 happy_x_3 of { happy_var_3 ->
happyIn50
(binOp happy_var_1 happy_var_2 happy_var_3
)}}}
happyReduce_107 = happySpecReduce_1 36# happyReduction_107
happyReduction_107 happy_x_1
= case happyOut56 happy_x_1 of { happy_var_1 ->
happyIn51
(mkEApp happy_var_1
)}
happyReduce_108 = happySpecReduce_2 36# happyReduction_108
happyReduction_108 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Minus) _)) ->
case happyOut51 happy_x_2 of { happy_var_2 ->
happyIn51
(at (happy_var_1,happy_var_2) $ EApp (at happy_var_1 (EVar (mkUnqual "negate"))) happy_var_2
)}}
happyReduce_109 = happySpecReduce_2 36# happyReduction_109
happyReduction_109 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Complement) _)) ->
case happyOut51 happy_x_2 of { happy_var_2 ->
happyIn51
(at (happy_var_1,happy_var_2) $ EApp (at happy_var_1 (EVar (mkUnqual "complement"))) happy_var_2
)}}
happyReduce_110 = happySpecReduce_1 37# happyReduction_110
happyReduction_110 happy_x_1
= case happyOut53 happy_x_1 of { happy_var_1 ->
happyIn52
(happy_var_1
)}
happyReduce_111 = happySpecReduce_1 37# happyReduction_111
happyReduction_111 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Op Other{} ) _))) ->
happyIn52
(let Token (Op (Other ns i)) _ = thing happy_var_1
in mkQual (mkModName ns) (mkInfix (T.toStrict i)) A.<$ happy_var_1
)}
happyReduce_112 = happySpecReduce_1 38# happyReduction_112
happyReduction_112 happy_x_1
= case happyOut54 happy_x_1 of { happy_var_1 ->
happyIn53
(happy_var_1
)}
happyReduce_113 = happySpecReduce_1 38# happyReduction_113
happyReduction_113 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Mul) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "*"
)}
happyReduce_114 = happySpecReduce_1 38# happyReduction_114
happyReduction_114 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Plus) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "+"
)}
happyReduce_115 = happySpecReduce_1 38# happyReduction_115
happyReduction_115 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Minus) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "-"
)}
happyReduce_116 = happySpecReduce_1 38# happyReduction_116
happyReduction_116 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Complement) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "~"
)}
happyReduce_117 = happySpecReduce_1 38# happyReduction_117
happyReduction_117 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Exp) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "^^"
)}
happyReduce_118 = happySpecReduce_1 38# happyReduction_118
happyReduction_118 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Hash) _)) ->
happyIn53
(Located happy_var_1 $ mkUnqual $ mkInfix "#"
)}
happyReduce_119 = happySpecReduce_1 39# happyReduction_119
happyReduction_119 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Op (Other [] _)) _))) ->
happyIn54
(let Token (Op (Other [] str)) _ = thing happy_var_1
in mkUnqual (mkInfix (T.toStrict str)) A.<$ happy_var_1
)}
happyReduce_120 = happySpecReduce_1 40# happyReduction_120
happyReduction_120 happy_x_1
= case happyOut53 happy_x_1 of { happy_var_1 ->
happyIn55
([happy_var_1]
)}
happyReduce_121 = happySpecReduce_3 40# happyReduction_121
happyReduction_121 happy_x_3
happy_x_2
happy_x_1
= case happyOut55 happy_x_1 of { happy_var_1 ->
case happyOut53 happy_x_3 of { happy_var_3 ->
happyIn55
(happy_var_3 : happy_var_1
)}}
happyReduce_122 = happySpecReduce_1 41# happyReduction_122
happyReduction_122 happy_x_1
= case happyOut57 happy_x_1 of { happy_var_1 ->
happyIn56
([happy_var_1]
)}
happyReduce_123 = happySpecReduce_2 41# happyReduction_123
happyReduction_123 happy_x_2
happy_x_1
= case happyOut56 happy_x_1 of { happy_var_1 ->
case happyOut57 happy_x_2 of { happy_var_2 ->
happyIn56
(happy_var_2 : happy_var_1
)}}
happyReduce_124 = happySpecReduce_1 42# happyReduction_124
happyReduction_124 happy_x_1
= case happyOut93 happy_x_1 of { happy_var_1 ->
happyIn57
(at happy_var_1 $ EVar (thing happy_var_1)
)}
happyReduce_125 = happySpecReduce_1 42# happyReduction_125
happyReduction_125 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Num {}) _))) ->
happyIn57
(at happy_var_1 $ numLit (tokenType (thing happy_var_1))
)}
happyReduce_126 = happySpecReduce_1 42# happyReduction_126
happyReduction_126 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (StrLit {}) _))) ->
happyIn57
(at happy_var_1 $ ELit $ ECString $ getStr happy_var_1
)}
happyReduce_127 = happySpecReduce_1 42# happyReduction_127
happyReduction_127 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (ChrLit {}) _))) ->
happyIn57
(at happy_var_1 $ ELit $ ECNum (getNum happy_var_1) CharLit
)}
happyReduce_128 = happySpecReduce_3 42# happyReduction_128
happyReduction_128 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut45 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_3) $ EParens happy_var_2
)}}}
happyReduce_129 = happySpecReduce_3 42# happyReduction_129
happyReduction_129 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut61 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_3) $ ETuple (reverse happy_var_2)
)}}}
happyReduce_130 = happySpecReduce_2 42# happyReduction_130
happyReduction_130 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym ParenR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_2) $ ETuple []
)}}
happyReduce_131 = happySpecReduce_2 42# happyReduction_131
happyReduction_131 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym CurlyR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_2) $ ERecord []
)}}
happyReduce_132 = happySpecReduce_3 42# happyReduction_132
happyReduction_132 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut63 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_3) $ ERecord (reverse happy_var_2)
)}}}
happyReduce_133 = happySpecReduce_2 42# happyReduction_133
happyReduction_133 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym BracketR) _)) ->
happyIn57
(at (happy_var_1,happy_var_2) $ EList []
)}}
happyReduce_134 = happySpecReduce_3 42# happyReduction_134
happyReduction_134 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOut64 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym BracketR) _)) ->
happyIn57
(at (happy_var_1,happy_var_3) happy_var_2
)}}}
happyReduce_135 = happySpecReduce_2 42# happyReduction_135
happyReduction_135 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BackTick) _)) ->
case happyOut95 happy_x_2 of { happy_var_2 ->
happyIn57
(at (happy_var_1,happy_var_2) $ ETypeVal happy_var_2
)}}
happyReduce_136 = happySpecReduce_3 42# happyReduction_136
happyReduction_136 happy_x_3
happy_x_2
happy_x_1
= case happyOut57 happy_x_1 of { happy_var_1 ->
case happyOut60 happy_x_3 of { happy_var_3 ->
happyIn57
(at (happy_var_1,happy_var_3) $ ESel happy_var_1 (thing happy_var_3)
)}}
happyReduce_137 = happySpecReduce_3 42# happyReduction_137
happyReduction_137 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut52 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn57
(at (happy_var_1,happy_var_3) $ EVar $ thing happy_var_2
)}}}
happyReduce_138 = happyMonadReduce 2# 42# happyReduction_138
happyReduction_138 (happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym TriL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym TriR ) _)) ->
( mkPoly (rComb happy_var_1 happy_var_2) [])}}
) (\r -> happyReturn (happyIn57 r))
happyReduce_139 = happyMonadReduce 3# 42# happyReduction_139
happyReduction_139 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym TriL ) _)) ->
case happyOut58 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym TriR ) _)) ->
( mkPoly (rComb happy_var_1 happy_var_3) happy_var_2)}}}
) (\r -> happyReturn (happyIn57 r))
happyReduce_140 = happySpecReduce_1 43# happyReduction_140
happyReduction_140 happy_x_1
= case happyOut59 happy_x_1 of { happy_var_1 ->
happyIn58
([happy_var_1]
)}
happyReduce_141 = happySpecReduce_3 43# happyReduction_141
happyReduction_141 happy_x_3
happy_x_2
happy_x_1
= case happyOut58 happy_x_1 of { happy_var_1 ->
case happyOut59 happy_x_3 of { happy_var_3 ->
happyIn58
(happy_var_3 : happy_var_1
)}}
happyReduce_142 = happyMonadReduce 1# 44# happyReduction_142
happyReduction_142 (happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Num {}) _))) ->
( polyTerm (srcRange happy_var_1) (getNum happy_var_1) 0)}
) (\r -> happyReturn (happyIn59 r))
happyReduce_143 = happyMonadReduce 1# 44# happyReduction_143
happyReduction_143 (happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_x) _)) ->
( polyTerm happy_var_1 1 1)}
) (\r -> happyReturn (happyIn59 r))
happyReduce_144 = happyMonadReduce 3# 44# happyReduction_144
happyReduction_144 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_x) _)) ->
case happyOutTok happy_x_3 of { (happy_var_3@(Located _ (Token (Num {}) _))) ->
( polyTerm (rComb happy_var_1 (srcRange happy_var_3))
1 (getNum happy_var_3))}}
) (\r -> happyReturn (happyIn59 r))
happyReduce_145 = happySpecReduce_1 45# happyReduction_145
happyReduction_145 happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
happyIn60
(fmap (`RecordSel` Nothing) happy_var_1
)}
happyReduce_146 = happyMonadReduce 1# 45# happyReduction_146
happyReduction_146 (happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Num {}) _))) ->
( mkTupleSel (srcRange happy_var_1) (getNum happy_var_1))}
) (\r -> happyReturn (happyIn60 r))
happyReduce_147 = happySpecReduce_3 46# happyReduction_147
happyReduction_147 happy_x_3
happy_x_2
happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn61
([ happy_var_3, happy_var_1]
)}}
happyReduce_148 = happySpecReduce_3 46# happyReduction_148
happyReduction_148 happy_x_3
happy_x_2
happy_x_1
= case happyOut61 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn61
(happy_var_3 : happy_var_1
)}}
happyReduce_149 = happySpecReduce_3 47# happyReduction_149
happyReduction_149 happy_x_3
happy_x_2
happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn62
(Named { name = happy_var_1, value = happy_var_3 }
)}}
happyReduce_150 = happyReduce 4# 47# happyReduction_150
happyReduction_150 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut39 happy_x_2 of { happy_var_2 ->
case happyOut45 happy_x_4 of { happy_var_4 ->
happyIn62
(Named { name = happy_var_1, value = EFun (reverse happy_var_2) happy_var_4 }
) `HappyStk` happyRest}}}
happyReduce_151 = happySpecReduce_1 48# happyReduction_151
happyReduction_151 happy_x_1
= case happyOut62 happy_x_1 of { happy_var_1 ->
happyIn63
([happy_var_1]
)}
happyReduce_152 = happySpecReduce_3 48# happyReduction_152
happyReduction_152 happy_x_3
happy_x_2
happy_x_1
= case happyOut63 happy_x_1 of { happy_var_1 ->
case happyOut62 happy_x_3 of { happy_var_3 ->
happyIn63
(happy_var_3 : happy_var_1
)}}
happyReduce_153 = happySpecReduce_3 49# happyReduction_153
happyReduction_153 happy_x_3
happy_x_2
happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut65 happy_x_3 of { happy_var_3 ->
happyIn64
(EComp happy_var_1 (reverse happy_var_3)
)}}
happyReduce_154 = happySpecReduce_1 49# happyReduction_154
happyReduction_154 happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
happyIn64
(EList [happy_var_1]
)}
happyReduce_155 = happySpecReduce_1 49# happyReduction_155
happyReduction_155 happy_x_1
= case happyOut61 happy_x_1 of { happy_var_1 ->
happyIn64
(EList (reverse happy_var_1)
)}
happyReduce_156 = happyMonadReduce 2# 49# happyReduction_156
happyReduction_156 (happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym DotDot ) _)) ->
( eFromTo happy_var_2 happy_var_1 Nothing Nothing)}}
) (\r -> happyReturn (happyIn64 r))
happyReduce_157 = happyMonadReduce 3# 49# happyReduction_157
happyReduction_157 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym DotDot ) _)) ->
case happyOut45 happy_x_3 of { happy_var_3 ->
( eFromTo happy_var_2 happy_var_1 Nothing (Just happy_var_3))}}}
) (\r -> happyReturn (happyIn64 r))
happyReduce_158 = happyMonadReduce 4# 49# happyReduction_158
happyReduction_158 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
case happyOutTok happy_x_4 of { (Located happy_var_4 (Token (Sym DotDot ) _)) ->
( eFromTo happy_var_4 happy_var_1 (Just happy_var_3) Nothing)}}}
) (\r -> happyReturn (happyIn64 r))
happyReduce_159 = happyMonadReduce 5# 49# happyReduction_159
happyReduction_159 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
case happyOutTok happy_x_4 of { (Located happy_var_4 (Token (Sym DotDot ) _)) ->
case happyOut45 happy_x_5 of { happy_var_5 ->
( eFromTo happy_var_4 happy_var_1 (Just happy_var_3) (Just happy_var_5))}}}}
) (\r -> happyReturn (happyIn64 r))
happyReduce_160 = happySpecReduce_2 49# happyReduction_160
happyReduction_160 happy_x_2
happy_x_1
= case happyOut45 happy_x_1 of { happy_var_1 ->
happyIn64
(EInfFrom happy_var_1 Nothing
)}
happyReduce_161 = happyReduce 4# 49# happyReduction_161
happyReduction_161 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut45 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn64
(EInfFrom happy_var_1 (Just happy_var_3)
) `HappyStk` happyRest}}
happyReduce_162 = happySpecReduce_1 50# happyReduction_162
happyReduction_162 happy_x_1
= case happyOut66 happy_x_1 of { happy_var_1 ->
happyIn65
([ reverse happy_var_1 ]
)}
happyReduce_163 = happySpecReduce_3 50# happyReduction_163
happyReduction_163 happy_x_3
happy_x_2
happy_x_1
= case happyOut65 happy_x_1 of { happy_var_1 ->
case happyOut66 happy_x_3 of { happy_var_3 ->
happyIn65
(reverse happy_var_3 : happy_var_1
)}}
happyReduce_164 = happySpecReduce_1 51# happyReduction_164
happyReduction_164 happy_x_1
= case happyOut67 happy_x_1 of { happy_var_1 ->
happyIn66
([happy_var_1]
)}
happyReduce_165 = happySpecReduce_3 51# happyReduction_165
happyReduction_165 happy_x_3
happy_x_2
happy_x_1
= case happyOut66 happy_x_1 of { happy_var_1 ->
case happyOut67 happy_x_3 of { happy_var_3 ->
happyIn66
(happy_var_3 : happy_var_1
)}}
happyReduce_166 = happySpecReduce_3 52# happyReduction_166
happyReduction_166 happy_x_3
happy_x_2
happy_x_1
= case happyOut68 happy_x_1 of { happy_var_1 ->
case happyOut45 happy_x_3 of { happy_var_3 ->
happyIn67
(Match happy_var_1 happy_var_3
)}}
happyReduce_167 = happySpecReduce_3 53# happyReduction_167
happyReduction_167 happy_x_3
happy_x_2
happy_x_1
= case happyOut69 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn68
(at (happy_var_1,happy_var_3) $ PTyped happy_var_1 happy_var_3
)}}
happyReduce_168 = happySpecReduce_1 53# happyReduction_168
happyReduction_168 happy_x_1
= case happyOut69 happy_x_1 of { happy_var_1 ->
happyIn68
(happy_var_1
)}
happyReduce_169 = happySpecReduce_3 54# happyReduction_169
happyReduction_169 happy_x_3
happy_x_2
happy_x_1
= case happyOut69 happy_x_1 of { happy_var_1 ->
case happyOut69 happy_x_3 of { happy_var_3 ->
happyIn69
(at (happy_var_1,happy_var_3) $ PSplit happy_var_1 happy_var_3
)}}
happyReduce_170 = happySpecReduce_1 54# happyReduction_170
happyReduction_170 happy_x_1
= case happyOut70 happy_x_1 of { happy_var_1 ->
happyIn69
(happy_var_1
)}
happyReduce_171 = happySpecReduce_1 55# happyReduction_171
happyReduction_171 happy_x_1
= case happyOut91 happy_x_1 of { happy_var_1 ->
happyIn70
(PVar happy_var_1
)}
happyReduce_172 = happySpecReduce_1 55# happyReduction_172
happyReduction_172 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym Underscore ) _)) ->
happyIn70
(at happy_var_1 $ PWild
)}
happyReduce_173 = happySpecReduce_2 55# happyReduction_173
happyReduction_173 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym ParenR ) _)) ->
happyIn70
(at (happy_var_1,happy_var_2) $ PTuple []
)}}
happyReduce_174 = happySpecReduce_3 55# happyReduction_174
happyReduction_174 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut68 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn70
(at (happy_var_1,happy_var_3) happy_var_2
)}}}
happyReduce_175 = happySpecReduce_3 55# happyReduction_175
happyReduction_175 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut71 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn70
(at (happy_var_1,happy_var_3) $ PTuple (reverse happy_var_2)
)}}}
happyReduce_176 = happySpecReduce_2 55# happyReduction_176
happyReduction_176 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym BracketR) _)) ->
happyIn70
(at (happy_var_1,happy_var_2) $ PList []
)}}
happyReduce_177 = happySpecReduce_3 55# happyReduction_177
happyReduction_177 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOut68 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym BracketR) _)) ->
happyIn70
(at (happy_var_1,happy_var_3) $ PList [happy_var_2]
)}}}
happyReduce_178 = happySpecReduce_3 55# happyReduction_178
happyReduction_178 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOut71 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym BracketR) _)) ->
happyIn70
(at (happy_var_1,happy_var_3) $ PList (reverse happy_var_2)
)}}}
happyReduce_179 = happySpecReduce_2 55# happyReduction_179
happyReduction_179 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym CurlyR ) _)) ->
happyIn70
(at (happy_var_1,happy_var_2) $ PRecord []
)}}
happyReduce_180 = happySpecReduce_3 55# happyReduction_180
happyReduction_180 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut73 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn70
(at (happy_var_1,happy_var_3) $ PRecord (reverse happy_var_2)
)}}}
happyReduce_181 = happySpecReduce_3 56# happyReduction_181
happyReduction_181 happy_x_3
happy_x_2
happy_x_1
= case happyOut68 happy_x_1 of { happy_var_1 ->
case happyOut68 happy_x_3 of { happy_var_3 ->
happyIn71
([happy_var_3, happy_var_1]
)}}
happyReduce_182 = happySpecReduce_3 56# happyReduction_182
happyReduction_182 happy_x_3
happy_x_2
happy_x_1
= case happyOut71 happy_x_1 of { happy_var_1 ->
case happyOut68 happy_x_3 of { happy_var_3 ->
happyIn71
(happy_var_3 : happy_var_1
)}}
happyReduce_183 = happySpecReduce_3 57# happyReduction_183
happyReduction_183 happy_x_3
happy_x_2
happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut68 happy_x_3 of { happy_var_3 ->
happyIn72
(Named { name = happy_var_1, value = happy_var_3 }
)}}
happyReduce_184 = happySpecReduce_1 58# happyReduction_184
happyReduction_184 happy_x_1
= case happyOut72 happy_x_1 of { happy_var_1 ->
happyIn73
([happy_var_1]
)}
happyReduce_185 = happySpecReduce_3 58# happyReduction_185
happyReduction_185 happy_x_3
happy_x_2
happy_x_1
= case happyOut73 happy_x_1 of { happy_var_1 ->
case happyOut72 happy_x_3 of { happy_var_3 ->
happyIn73
(happy_var_3 : happy_var_1
)}}
happyReduce_186 = happySpecReduce_1 59# happyReduction_186
happyReduction_186 happy_x_1
= case happyOut82 happy_x_1 of { happy_var_1 ->
happyIn74
(at happy_var_1 $ mkSchema [] [] happy_var_1
)}
happyReduce_187 = happySpecReduce_2 59# happyReduction_187
happyReduction_187 happy_x_2
happy_x_1
= case happyOut75 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_2 of { happy_var_2 ->
happyIn74
(at (happy_var_1,happy_var_2) $ mkSchema (thing happy_var_1) [] happy_var_2
)}}
happyReduce_188 = happySpecReduce_2 59# happyReduction_188
happyReduction_188 happy_x_2
happy_x_1
= case happyOut76 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_2 of { happy_var_2 ->
happyIn74
(at (happy_var_1,happy_var_2) $ mkSchema [] (thing happy_var_1) happy_var_2
)}}
happyReduce_189 = happySpecReduce_3 59# happyReduction_189
happyReduction_189 happy_x_3
happy_x_2
happy_x_1
= case happyOut75 happy_x_1 of { happy_var_1 ->
case happyOut76 happy_x_2 of { happy_var_2 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn74
(at (happy_var_1,happy_var_3) $ mkSchema (thing happy_var_1)
(thing happy_var_2) happy_var_3
)}}}
happyReduce_190 = happySpecReduce_2 60# happyReduction_190
happyReduction_190 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym CurlyR ) _)) ->
happyIn75
(Located (rComb happy_var_1 happy_var_2) []
)}}
happyReduce_191 = happySpecReduce_3 60# happyReduction_191
happyReduction_191 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut79 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn75
(Located (rComb happy_var_1 happy_var_3) (reverse happy_var_2)
)}}}
happyReduce_192 = happyMonadReduce 2# 61# happyReduction_192
happyReduction_192 (happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut82 happy_x_1 of { happy_var_1 ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym FatArrR ) _)) ->
( fmap (\x -> at (x,happy_var_2) x) (mkProp happy_var_1))}}
) (\r -> happyReturn (happyIn76 r))
happyReduce_193 = happySpecReduce_1 62# happyReduction_193
happyReduction_193 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Hash) _)) ->
happyIn77
(Located happy_var_1 KNum
)}
happyReduce_194 = happySpecReduce_1 62# happyReduction_194
happyReduction_194 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Op Mul) _)) ->
happyIn77
(Located happy_var_1 KType
)}
happyReduce_195 = happyMonadReduce 1# 63# happyReduction_195
happyReduction_195 (happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut90 happy_x_1 of { happy_var_1 ->
( mkTParam happy_var_1 Nothing)}
) (\r -> happyReturn (happyIn78 r))
happyReduce_196 = happyMonadReduce 3# 63# happyReduction_196
happyReduction_196 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut77 happy_x_3 of { happy_var_3 ->
( mkTParam (at (happy_var_1,happy_var_3) happy_var_1) (Just (thing happy_var_3)))}}
) (\r -> happyReturn (happyIn78 r))
happyReduce_197 = happySpecReduce_1 64# happyReduction_197
happyReduction_197 happy_x_1
= case happyOut78 happy_x_1 of { happy_var_1 ->
happyIn79
([happy_var_1]
)}
happyReduce_198 = happySpecReduce_3 64# happyReduction_198
happyReduction_198 happy_x_3
happy_x_2
happy_x_1
= case happyOut79 happy_x_1 of { happy_var_1 ->
case happyOut78 happy_x_3 of { happy_var_3 ->
happyIn79
(happy_var_3 : happy_var_1
)}}
happyReduce_199 = happyMonadReduce 1# 65# happyReduction_199
happyReduction_199 (happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOut90 happy_x_1 of { happy_var_1 ->
( mkTParam happy_var_1 Nothing)}
) (\r -> happyReturn (happyIn80 r))
happyReduce_200 = happyMonadReduce 5# 65# happyReduction_200
happyReduction_200 (happy_x_5 `HappyStk`
happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut90 happy_x_2 of { happy_var_2 ->
case happyOut77 happy_x_4 of { happy_var_4 ->
case happyOutTok happy_x_5 of { (Located happy_var_5 (Token (Sym ParenR ) _)) ->
( mkTParam (at (happy_var_1,happy_var_5) happy_var_2) (Just (thing happy_var_4)))}}}}
) (\r -> happyReturn (happyIn80 r))
happyReduce_201 = happySpecReduce_1 66# happyReduction_201
happyReduction_201 happy_x_1
= case happyOut80 happy_x_1 of { happy_var_1 ->
happyIn81
([happy_var_1]
)}
happyReduce_202 = happySpecReduce_2 66# happyReduction_202
happyReduction_202 happy_x_2
happy_x_1
= case happyOut81 happy_x_1 of { happy_var_1 ->
case happyOut80 happy_x_2 of { happy_var_2 ->
happyIn81
(happy_var_2 : happy_var_1
)}}
happyReduce_203 = happySpecReduce_3 67# happyReduction_203
happyReduction_203 happy_x_3
happy_x_2
happy_x_1
= case happyOut83 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn82
(at (happy_var_1,happy_var_3) $ TFun happy_var_1 happy_var_3
)}}
happyReduce_204 = happySpecReduce_3 67# happyReduction_204
happyReduction_204 happy_x_3
happy_x_2
happy_x_1
= case happyOut82 happy_x_1 of { happy_var_1 ->
case happyOut53 happy_x_2 of { happy_var_2 ->
case happyOut83 happy_x_3 of { happy_var_3 ->
happyIn82
(at (happy_var_1,happy_var_3) $ TInfix happy_var_1 happy_var_2 defaultFixity happy_var_3
)}}}
happyReduce_205 = happySpecReduce_1 67# happyReduction_205
happyReduction_205 happy_x_1
= case happyOut83 happy_x_1 of { happy_var_1 ->
happyIn82
(happy_var_1
)}
happyReduce_206 = happySpecReduce_2 68# happyReduction_206
happyReduction_206 happy_x_2
happy_x_1
= case happyOut86 happy_x_1 of { happy_var_1 ->
case happyOut84 happy_x_2 of { happy_var_2 ->
happyIn83
(at (happy_var_1,happy_var_2) $ foldr TSeq happy_var_2 (reverse (thing happy_var_1))
)}}
happyReduce_207 = happySpecReduce_2 68# happyReduction_207
happyReduction_207 happy_x_2
happy_x_1
= case happyOut93 happy_x_1 of { happy_var_1 ->
case happyOut85 happy_x_2 of { happy_var_2 ->
happyIn83
(at (happy_var_1,head happy_var_2)
$ TUser (thing happy_var_1) (reverse happy_var_2)
)}}
happyReduce_208 = happySpecReduce_1 68# happyReduction_208
happyReduction_208 happy_x_1
= case happyOut84 happy_x_1 of { happy_var_1 ->
happyIn83
(happy_var_1
)}
happyReduce_209 = happySpecReduce_1 69# happyReduction_209
happyReduction_209 happy_x_1
= case happyOut93 happy_x_1 of { happy_var_1 ->
happyIn84
(at happy_var_1 $ TUser (thing happy_var_1) []
)}
happyReduce_210 = happySpecReduce_1 69# happyReduction_210
happyReduction_210 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Num {}) _))) ->
happyIn84
(at happy_var_1 $ TNum (getNum happy_var_1)
)}
happyReduce_211 = happySpecReduce_1 69# happyReduction_211
happyReduction_211 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (ChrLit {}) _))) ->
happyIn84
(at happy_var_1 $ TChar (toEnum $ fromInteger
$ getNum happy_var_1)
)}
happyReduce_212 = happySpecReduce_3 69# happyReduction_212
happyReduction_212 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOut82 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym BracketR) _)) ->
happyIn84
(at (happy_var_1,happy_var_3) $ TSeq happy_var_2 TBit
)}}}
happyReduce_213 = happySpecReduce_3 69# happyReduction_213
happyReduction_213 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut82 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn84
(at (happy_var_1,happy_var_3) $ TParens happy_var_2
)}}}
happyReduce_214 = happySpecReduce_2 69# happyReduction_214
happyReduction_214 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym ParenR ) _)) ->
happyIn84
(at (happy_var_1,happy_var_2) $ TTuple []
)}}
happyReduce_215 = happySpecReduce_3 69# happyReduction_215
happyReduction_215 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut87 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
happyIn84
(at (happy_var_1,happy_var_3) $ TTuple (reverse happy_var_2)
)}}}
happyReduce_216 = happySpecReduce_2 69# happyReduction_216
happyReduction_216 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym CurlyR ) _)) ->
happyIn84
(at (happy_var_1,happy_var_2) $ TRecord []
)}}
happyReduce_217 = happySpecReduce_3 69# happyReduction_217
happyReduction_217 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut89 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn84
(at (happy_var_1,happy_var_3) $ TRecord (reverse happy_var_2)
)}}}
happyReduce_218 = happySpecReduce_1 69# happyReduction_218
happyReduction_218 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym Underscore ) _)) ->
happyIn84
(at happy_var_1 TWild
)}
happyReduce_219 = happySpecReduce_1 70# happyReduction_219
happyReduction_219 happy_x_1
= case happyOut84 happy_x_1 of { happy_var_1 ->
happyIn85
([ happy_var_1 ]
)}
happyReduce_220 = happySpecReduce_2 70# happyReduction_220
happyReduction_220 happy_x_2
happy_x_1
= case happyOut85 happy_x_1 of { happy_var_1 ->
case happyOut84 happy_x_2 of { happy_var_2 ->
happyIn85
(happy_var_2 : happy_var_1
)}}
happyReduce_221 = happySpecReduce_3 71# happyReduction_221
happyReduction_221 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym BracketL) _)) ->
case happyOut82 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym BracketR) _)) ->
happyIn86
(Located (rComb happy_var_1 happy_var_3) [ happy_var_2 ]
)}}}
happyReduce_222 = happyReduce 4# 71# happyReduction_222
happyReduction_222 (happy_x_4 `HappyStk`
happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest)
= case happyOut86 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
case happyOutTok happy_x_4 of { (Located happy_var_4 (Token (Sym BracketR) _)) ->
happyIn86
(at (happy_var_1,happy_var_4) (fmap (happy_var_3 :) happy_var_1)
) `HappyStk` happyRest}}}
happyReduce_223 = happySpecReduce_3 72# happyReduction_223
happyReduction_223 happy_x_3
happy_x_2
happy_x_1
= case happyOut82 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn87
([ happy_var_3, happy_var_1]
)}}
happyReduce_224 = happySpecReduce_3 72# happyReduction_224
happyReduction_224 happy_x_3
happy_x_2
happy_x_1
= case happyOut87 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn87
(happy_var_3 : happy_var_1
)}}
happyReduce_225 = happySpecReduce_3 73# happyReduction_225
happyReduction_225 happy_x_3
happy_x_2
happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn88
(Named { name = happy_var_1, value = happy_var_3 }
)}}
happyReduce_226 = happySpecReduce_1 74# happyReduction_226
happyReduction_226 happy_x_1
= case happyOut88 happy_x_1 of { happy_var_1 ->
happyIn89
([happy_var_1]
)}
happyReduce_227 = happySpecReduce_3 74# happyReduction_227
happyReduction_227 happy_x_3
happy_x_2
happy_x_1
= case happyOut89 happy_x_1 of { happy_var_1 ->
case happyOut88 happy_x_3 of { happy_var_3 ->
happyIn89
(happy_var_3 : happy_var_1
)}}
happyReduce_228 = happySpecReduce_1 75# happyReduction_228
happyReduction_228 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Ident [] _) _))) ->
happyIn90
(let Token (Ident _ str) _ = thing happy_var_1
in happy_var_1 { thing = mkIdent (T.toStrict str) }
)}
happyReduce_229 = happySpecReduce_1 75# happyReduction_229
happyReduction_229 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_x) _)) ->
happyIn90
(Located { srcRange = happy_var_1, thing = mkIdent "x" }
)}
happyReduce_230 = happySpecReduce_1 75# happyReduction_230
happyReduction_230 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_private) _)) ->
happyIn90
(Located { srcRange = happy_var_1, thing = mkIdent "private" }
)}
happyReduce_231 = happySpecReduce_1 75# happyReduction_231
happyReduction_231 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_as) _)) ->
happyIn90
(Located { srcRange = happy_var_1, thing = mkIdent "as" }
)}
happyReduce_232 = happySpecReduce_1 75# happyReduction_232
happyReduction_232 happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (KW KW_hiding) _)) ->
happyIn90
(Located { srcRange = happy_var_1, thing = mkIdent "hiding" }
)}
happyReduce_233 = happySpecReduce_1 76# happyReduction_233
happyReduction_233 happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
happyIn91
(fmap mkUnqual happy_var_1
)}
happyReduce_234 = happySpecReduce_1 77# happyReduction_234
happyReduction_234 happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
happyIn92
(fmap identText happy_var_1
)}
happyReduce_235 = happySpecReduce_1 77# happyReduction_235
happyReduction_235 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token Ident{} _))) ->
happyIn92
(let Token (Ident ns i) _ = thing happy_var_1
in mkModName (ns ++ [i]) A.<$ happy_var_1
)}
happyReduce_236 = happySpecReduce_1 78# happyReduction_236
happyReduction_236 happy_x_1
= case happyOut91 happy_x_1 of { happy_var_1 ->
happyIn93
(happy_var_1
)}
happyReduce_237 = happySpecReduce_1 78# happyReduction_237
happyReduction_237 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token Ident{} _))) ->
happyIn93
(let Token (Ident ns i) _ = thing happy_var_1
in mkQual (mkModName ns) (mkIdent (T.toStrict i)) A.<$ happy_var_1
)}
happyReduce_238 = happySpecReduce_1 79# happyReduction_238
happyReduction_238 happy_x_1
= case happyOut93 happy_x_1 of { happy_var_1 ->
happyIn94
(happy_var_1
)}
happyReduce_239 = happySpecReduce_1 79# happyReduction_239
happyReduction_239 happy_x_1
= case happyOut52 happy_x_1 of { happy_var_1 ->
happyIn94
(happy_var_1
)}
happyReduce_240 = happySpecReduce_3 79# happyReduction_240
happyReduction_240 happy_x_3
happy_x_2
happy_x_1
= case happyOut52 happy_x_2 of { happy_var_2 ->
happyIn94
(happy_var_2
)}
happyReduce_241 = happySpecReduce_1 80# happyReduction_241
happyReduction_241 happy_x_1
= case happyOut93 happy_x_1 of { happy_var_1 ->
happyIn95
(at happy_var_1 $ TUser (thing happy_var_1) []
)}
happyReduce_242 = happySpecReduce_1 80# happyReduction_242
happyReduction_242 happy_x_1
= case happyOutTok happy_x_1 of { (happy_var_1@(Located _ (Token (Num {}) _))) ->
happyIn95
(at happy_var_1 $ TNum (getNum happy_var_1)
)}
happyReduce_243 = happyMonadReduce 3# 80# happyReduction_243
happyReduction_243 (happy_x_3 `HappyStk`
happy_x_2 `HappyStk`
happy_x_1 `HappyStk`
happyRest) tk
= happyThen (case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym ParenL ) _)) ->
case happyOut82 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym ParenR ) _)) ->
( validDemotedType (rComb happy_var_1 happy_var_3) happy_var_2)}}}
) (\r -> happyReturn (happyIn95 r))
happyReduce_244 = happySpecReduce_2 80# happyReduction_244
happyReduction_244 happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOutTok happy_x_2 of { (Located happy_var_2 (Token (Sym CurlyR ) _)) ->
happyIn95
(at (happy_var_1,happy_var_2) (TRecord [])
)}}
happyReduce_245 = happySpecReduce_3 80# happyReduction_245
happyReduction_245 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut97 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn95
(at (happy_var_1,happy_var_3) (TRecord (reverse happy_var_2))
)}}}
happyReduce_246 = happySpecReduce_3 80# happyReduction_246
happyReduction_246 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut82 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn95
(anonRecord (getLoc (happy_var_1,happy_var_3)) [happy_var_2]
)}}}
happyReduce_247 = happySpecReduce_3 80# happyReduction_247
happyReduction_247 happy_x_3
happy_x_2
happy_x_1
= case happyOutTok happy_x_1 of { (Located happy_var_1 (Token (Sym CurlyL ) _)) ->
case happyOut87 happy_x_2 of { happy_var_2 ->
case happyOutTok happy_x_3 of { (Located happy_var_3 (Token (Sym CurlyR ) _)) ->
happyIn95
(anonRecord (getLoc (happy_var_1,happy_var_3)) (reverse happy_var_2)
)}}}
happyReduce_248 = happySpecReduce_3 81# happyReduction_248
happyReduction_248 happy_x_3
happy_x_2
happy_x_1
= case happyOut90 happy_x_1 of { happy_var_1 ->
case happyOut82 happy_x_3 of { happy_var_3 ->
happyIn96
(Named { name = happy_var_1, value = happy_var_3 }
)}}
happyReduce_249 = happySpecReduce_1 82# happyReduction_249
happyReduction_249 happy_x_1
= case happyOut96 happy_x_1 of { happy_var_1 ->
happyIn97
([happy_var_1]
)}
happyReduce_250 = happySpecReduce_3 82# happyReduction_250
happyReduction_250 happy_x_3
happy_x_2
happy_x_1
= case happyOut97 happy_x_1 of { happy_var_1 ->
case happyOut96 happy_x_3 of { happy_var_3 ->
happyIn97
(happy_var_3 : happy_var_1
)}}
happyNewToken action sts stk
= lexerP(\tk ->
let cont i = happyDoAction i tk action sts stk in
case tk of {
Located _ (Token EOF _) -> happyDoAction 59# tk action sts stk;
happy_dollar_dollar@(Located _ (Token (Num {}) _)) -> cont 1#;
happy_dollar_dollar@(Located _ (Token (StrLit {}) _)) -> cont 2#;
happy_dollar_dollar@(Located _ (Token (ChrLit {}) _)) -> cont 3#;
happy_dollar_dollar@(Located _ (Token (Ident [] _) _)) -> cont 4#;
happy_dollar_dollar@(Located _ (Token Ident{} _)) -> cont 5#;
Located happy_dollar_dollar (Token (KW KW_include) _) -> cont 6#;
Located happy_dollar_dollar (Token (KW KW_import) _) -> cont 7#;
Located happy_dollar_dollar (Token (KW KW_as) _) -> cont 8#;
Located happy_dollar_dollar (Token (KW KW_hiding) _) -> cont 9#;
Located happy_dollar_dollar (Token (KW KW_private) _) -> cont 10#;
Located happy_dollar_dollar (Token (KW KW_property) _) -> cont 11#;
Located happy_dollar_dollar (Token (KW KW_infix) _) -> cont 12#;
Located happy_dollar_dollar (Token (KW KW_infixl) _) -> cont 13#;
Located happy_dollar_dollar (Token (KW KW_infixr) _) -> cont 14#;
Located happy_dollar_dollar (Token (KW KW_type ) _) -> cont 15#;
Located happy_dollar_dollar (Token (KW KW_newtype) _) -> cont 16#;
Located happy_dollar_dollar (Token (KW KW_module ) _) -> cont 17#;
Located happy_dollar_dollar (Token (KW KW_where ) _) -> cont 18#;
Located happy_dollar_dollar (Token (KW KW_let ) _) -> cont 19#;
Located happy_dollar_dollar (Token (KW KW_if ) _) -> cont 20#;
Located happy_dollar_dollar (Token (KW KW_then ) _) -> cont 21#;
Located happy_dollar_dollar (Token (KW KW_else ) _) -> cont 22#;
Located happy_dollar_dollar (Token (KW KW_x) _) -> cont 23#;
Located happy_dollar_dollar (Token (KW KW_primitive) _) -> cont 24#;
Located happy_dollar_dollar (Token (Sym BracketL) _) -> cont 25#;
Located happy_dollar_dollar (Token (Sym BracketR) _) -> cont 26#;
Located happy_dollar_dollar (Token (Sym ArrL ) _) -> cont 27#;
Located happy_dollar_dollar (Token (Sym DotDot ) _) -> cont 28#;
Located happy_dollar_dollar (Token (Sym DotDotDot) _) -> cont 29#;
Located happy_dollar_dollar (Token (Sym Bar ) _) -> cont 30#;
Located happy_dollar_dollar (Token (Sym ParenL ) _) -> cont 31#;
Located happy_dollar_dollar (Token (Sym ParenR ) _) -> cont 32#;
Located happy_dollar_dollar (Token (Sym Comma ) _) -> cont 33#;
Located happy_dollar_dollar (Token (Sym Semi ) _) -> cont 34#;
Located happy_dollar_dollar (Token (Sym Dot ) _) -> cont 35#;
Located happy_dollar_dollar (Token (Sym CurlyL ) _) -> cont 36#;
Located happy_dollar_dollar (Token (Sym CurlyR ) _) -> cont 37#;
Located happy_dollar_dollar (Token (Sym TriL ) _) -> cont 38#;
Located happy_dollar_dollar (Token (Sym TriR ) _) -> cont 39#;
Located happy_dollar_dollar (Token (Sym EqDef ) _) -> cont 40#;
Located happy_dollar_dollar (Token (Sym BackTick) _) -> cont 41#;
Located happy_dollar_dollar (Token (Sym Colon ) _) -> cont 42#;
Located happy_dollar_dollar (Token (Sym ArrR ) _) -> cont 43#;
Located happy_dollar_dollar (Token (Sym FatArrR ) _) -> cont 44#;
Located happy_dollar_dollar (Token (Sym Lambda ) _) -> cont 45#;
Located happy_dollar_dollar (Token (Sym Underscore ) _) -> cont 46#;
Located happy_dollar_dollar (Token (Virt VCurlyL) _) -> cont 47#;
Located happy_dollar_dollar (Token (Virt VCurlyR) _) -> cont 48#;
Located happy_dollar_dollar (Token (Virt VSemi) _) -> cont 49#;
Located happy_dollar_dollar (Token (Op Plus) _) -> cont 50#;
Located happy_dollar_dollar (Token (Op Mul) _) -> cont 51#;
Located happy_dollar_dollar (Token (Op Exp) _) -> cont 52#;
Located happy_dollar_dollar (Token (Op Minus) _) -> cont 53#;
Located happy_dollar_dollar (Token (Op Complement) _) -> cont 54#;
Located happy_dollar_dollar (Token (Op Hash) _) -> cont 55#;
happy_dollar_dollar@(Located _ (Token (Op (Other [] _)) _)) -> cont 56#;
happy_dollar_dollar@(Located _ (Token (Op Other{} ) _)) -> cont 57#;
happy_dollar_dollar@(Located _ (Token (White DocStr) _)) -> cont 58#;
_ -> happyError' tk
})
happyError_ 59# tk = happyError' tk
happyError_ _ tk = happyError' tk
happyThen :: () => ParseM a -> (a -> ParseM b) -> ParseM b
happyThen = (>>=)
happyReturn :: () => a -> ParseM a
happyReturn = (return)
happyThen1 = happyThen
happyReturn1 :: () => a -> ParseM a
happyReturn1 = happyReturn
happyError' :: () => (Located Token) -> ParseM a
happyError' tk = (\token -> happyError) tk
vmodule = happySomeParser where
happySomeParser = happyThen (happyParse 0#) (\x -> happyReturn (happyOut15 x))
program = happySomeParser where
happySomeParser = happyThen (happyParse 1#) (\x -> happyReturn (happyOut23 x))
programLayout = happySomeParser where
happySomeParser = happyThen (happyParse 2#) (\x -> happyReturn (happyOut24 x))
expr = happySomeParser where
happySomeParser = happyThen (happyParse 3#) (\x -> happyReturn (happyOut45 x))
decl = happySomeParser where
happySomeParser = happyThen (happyParse 4#) (\x -> happyReturn (happyOut33 x))
decls = happySomeParser where
happySomeParser = happyThen (happyParse 5#) (\x -> happyReturn (happyOut41 x))
declsLayout = happySomeParser where
happySomeParser = happyThen (happyParse 6#) (\x -> happyReturn (happyOut43 x))
letDecl = happySomeParser where
happySomeParser = happyThen (happyParse 7#) (\x -> happyReturn (happyOut34 x))
repl = happySomeParser where
happySomeParser = happyThen (happyParse 8#) (\x -> happyReturn (happyOut44 x))
schema = happySomeParser where
happySomeParser = happyThen (happyParse 9#) (\x -> happyReturn (happyOut74 x))
modName = happySomeParser where
happySomeParser = happyThen (happyParse 10#) (\x -> happyReturn (happyOut92 x))
helpName = happySomeParser where
happySomeParser = happyThen (happyParse 11#) (\x -> happyReturn (happyOut94 x))
happySeq = happyDontSeq
parseModName :: String -> Maybe ModName
parseModName txt =
case parseString defaultConfig { cfgModuleScope = False } modName txt of
Right a -> Just (thing a)
Left _ -> Nothing
parseHelpName :: String -> Maybe PName
parseHelpName txt =
case parseString defaultConfig { cfgModuleScope = False } helpName txt of
Right a -> Just (thing a)
Left _ -> Nothing
addImplicitIncludes :: Config -> Program PName -> Program PName
addImplicitIncludes cfg (Program ds) =
Program $ map path (cfgAutoInclude cfg) ++ ds
where path p = Include Located { srcRange = rng, thing = p }
rng = Range { source = cfgSource cfg, from = start, to = start }
parseProgramWith :: Config -> Text -> Either ParseError (Program PName)
parseProgramWith cfg s = case res s of
Left err -> Left err
Right a -> Right (addImplicitIncludes cfg a)
where
res = parse cfg $ case cfgLayout cfg of
Layout -> programLayout
NoLayout -> program
parseModule :: Config -> Text -> Either ParseError (Module PName)
parseModule cfg = parse cfg { cfgModuleScope = True } vmodule
parseProgram :: Layout -> Text -> Either ParseError (Program PName)
parseProgram l = parseProgramWith defaultConfig { cfgLayout = l }
parseExprWith :: Config -> Text -> Either ParseError (Expr PName)
parseExprWith cfg = parse cfg { cfgModuleScope = False } expr
parseExpr :: Text -> Either ParseError (Expr PName)
parseExpr = parseExprWith defaultConfig
parseDeclWith :: Config -> Text -> Either ParseError (Decl PName)
parseDeclWith cfg = parse cfg { cfgModuleScope = False } decl
parseDecl :: Text -> Either ParseError (Decl PName)
parseDecl = parseDeclWith defaultConfig
parseDeclsWith :: Config -> Text -> Either ParseError [Decl PName]
parseDeclsWith cfg = parse cfg { cfgModuleScope = ms } decls'
where (ms, decls') = case cfgLayout cfg of
Layout -> (True, declsLayout)
NoLayout -> (False, decls)
parseDecls :: Text -> Either ParseError [Decl PName]
parseDecls = parseDeclsWith defaultConfig
parseLetDeclWith :: Config -> Text -> Either ParseError (Decl PName)
parseLetDeclWith cfg = parse cfg { cfgModuleScope = False } letDecl
parseLetDecl :: Text -> Either ParseError (Decl PName)
parseLetDecl = parseLetDeclWith defaultConfig
parseReplWith :: Config -> Text -> Either ParseError (ReplInput PName)
parseReplWith cfg = parse cfg { cfgModuleScope = False } repl
parseRepl :: Text -> Either ParseError (ReplInput PName)
parseRepl = parseReplWith defaultConfig
parseSchemaWith :: Config -> Text -> Either ParseError (Schema PName)
parseSchemaWith cfg = parse cfg { cfgModuleScope = False } schema
parseSchema :: Text -> Either ParseError (Schema PName)
parseSchema = parseSchemaWith defaultConfig
-- vim: ft=haskell
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "" #-}
{-# LINE 19 "" #-}
{-# LINE 1 "/usr/local/Cellar/ghc/7.10.3b/lib/ghc-7.10.3/include/ghcversion.h" #-}
{-# LINE 20 "" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp
{-# LINE 13 "templates/GenericTemplate.hs" #-}
-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ > 706
#define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Bool)
#define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Bool)
#define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Bool)
#else
#define LT(n,m) (n Happy_GHC_Exts.<# m)
#define GTE(n,m) (n Happy_GHC_Exts.>=# m)
#define EQ(n,m) (n Happy_GHC_Exts.==# m)
#endif
{-# LINE 46 "templates/GenericTemplate.hs" #-}
data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList
{-# LINE 67 "templates/GenericTemplate.hs" #-}
{-# LINE 77 "templates/GenericTemplate.hs" #-}
infixr 9 `HappyStk`
data HappyStk a = HappyStk a (HappyStk a)
-----------------------------------------------------------------------------
-- starting the parse
happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll
-----------------------------------------------------------------------------
-- Accepting the parse
-- If the current token is 0#, it means we've just accepted a partial
-- parse (a %partial parser). We must ignore the saved token on the top of
-- the stack in this case.
happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
happyReturn1 ans
happyAccept j tk st sts (HappyStk ans _) =
(happyTcHack j (happyTcHack st)) (happyReturn1 ans)
-----------------------------------------------------------------------------
-- Arrays only: do the next action
happyDoAction i tk st
= {- nothing -}
case action of
0# -> {- nothing -}
happyFail i tk st
-1# -> {- nothing -}
happyAccept i tk st
n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}
(happyReduceArr Happy_Data_Array.! rule) i tk st
where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
n -> {- nothing -}
happyShift new_state i tk st
where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
where off = indexShortOffAddr happyActOffsets st
off_i = (off Happy_GHC_Exts.+# i)
check = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#))
then EQ(indexShortOffAddr happyCheck off_i, i)
else False
action
| check = indexShortOffAddr happyTable off_i
| otherwise = indexShortOffAddr happyDefActions st
indexShortOffAddr (HappyA# arr) off =
Happy_GHC_Exts.narrow16Int# i
where
i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low)
high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#)))
low = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off'))
off' = off Happy_GHC_Exts.*# 2#
data HappyAddr = HappyA# Happy_GHC_Exts.Addr#
-----------------------------------------------------------------------------
-- HappyState data type (not arrays)
{-# LINE 170 "templates/GenericTemplate.hs" #-}
-----------------------------------------------------------------------------
-- Shifting a token
happyShift new_state 0# tk st sts stk@(x `HappyStk` _) =
let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
-- trace "shifting the error token" $
happyDoAction i tk new_state (HappyCons (st) (sts)) (stk)
happyShift new_state i tk st sts stk =
happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk)
-- happyReduce is specialised for the common cases.
happySpecReduce_0 i fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happySpecReduce_0 nt fn j tk st@((action)) sts stk
= happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk)
happySpecReduce_1 i fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk')
= let r = fn v1 in
happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
happySpecReduce_2 i fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk')
= let r = fn v1 v2 in
happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
happySpecReduce_3 i fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
= let r = fn v1 v2 v3 in
happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
happyReduce k i fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happyReduce k nt fn j tk st sts stk
= case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of
sts1@((HappyCons (st1@(action)) (_))) ->
let r = fn stk in -- it doesn't hurt to always seq here...
happyDoSeq r (happyGoto nt j tk st1 sts1 r)
happyMonadReduce k nt fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happyMonadReduce k nt fn j tk st sts stk =
case happyDrop k (HappyCons (st) (sts)) of
sts1@((HappyCons (st1@(action)) (_))) ->
let drop_stk = happyDropStk k stk in
happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))
happyMonad2Reduce k nt fn 0# tk st sts stk
= happyFail 0# tk st sts stk
happyMonad2Reduce k nt fn j tk st sts stk =
case happyDrop k (HappyCons (st) (sts)) of
sts1@((HappyCons (st1@(action)) (_))) ->
let drop_stk = happyDropStk k stk
off = indexShortOffAddr happyGotoOffsets st1
off_i = (off Happy_GHC_Exts.+# nt)
new_state = indexShortOffAddr happyTable off_i
in
happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))
happyDrop 0# l = l
happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t
happyDropStk 0# l = l
happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs
-----------------------------------------------------------------------------
-- Moving to a new state after a reduction
happyGoto nt j tk st =
{- nothing -}
happyDoAction j tk new_state
where off = indexShortOffAddr happyGotoOffsets st
off_i = (off Happy_GHC_Exts.+# nt)
new_state = indexShortOffAddr happyTable off_i
-----------------------------------------------------------------------------
-- Error recovery (0# is the error token)
-- parse error if we are in recovery and we fail again
happyFail 0# tk old_st _ stk@(x `HappyStk` _) =
let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
-- trace "failing" $
happyError_ i tk
{- We don't need state discarding for our restricted implementation of
"error". In fact, it can cause some bogus parses, so I've disabled it
for now --SDM
-- discard a state
happyFail 0# tk old_st (HappyCons ((action)) (sts))
(saved_tok `HappyStk` _ `HappyStk` stk) =
-- trace ("discarding state, depth " ++ show (length stk)) $
happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk))
-}
-- Enter error recovery: generate an error token,
-- save the old token and carry on.
happyFail i tk (action) sts stk =
-- trace "entering error recovery" $
happyDoAction 0# tk action sts ( (Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk)
-- Internal happy errors:
notHappyAtAll :: a
notHappyAtAll = error "Internal Happy error\n"
-----------------------------------------------------------------------------
-- Hack to get the typechecker to accept our action functions
happyTcHack :: Happy_GHC_Exts.Int# -> a -> a
happyTcHack x y = y
{-# INLINE happyTcHack #-}
-----------------------------------------------------------------------------
-- Seq-ing. If the --strict flag is given, then Happy emits
-- happySeq = happyDoSeq
-- otherwise it emits
-- happySeq = happyDontSeq
happyDoSeq, happyDontSeq :: a -> b -> b
happyDoSeq a b = a `seq` b
happyDontSeq a b = b
-----------------------------------------------------------------------------
-- Don't inline any functions from the template. GHC has a nasty habit
-- of deciding to inline happyGoto everywhere, which increases the size of
-- the generated parser quite a bit.
{-# NOINLINE happyDoAction #-}
{-# NOINLINE happyTable #-}
{-# NOINLINE happyCheck #-}
{-# NOINLINE happyActOffsets #-}
{-# NOINLINE happyGotoOffsets #-}
{-# NOINLINE happyDefActions #-}
{-# NOINLINE happyShift #-}
{-# NOINLINE happySpecReduce_0 #-}
{-# NOINLINE happySpecReduce_1 #-}
{-# NOINLINE happySpecReduce_2 #-}
{-# NOINLINE happySpecReduce_3 #-}
{-# NOINLINE happyReduce #-}
{-# NOINLINE happyMonadReduce #-}
{-# NOINLINE happyGoto #-}
{-# NOINLINE happyFail #-}
-- end of Happy Template.
cryptol-2.4.0/dist/build/Cryptol/Parser/ 0000755 0000000 0000000 00000000000 12737220175 016337 5 ustar 00 0000000 0000000 cryptol-2.4.0/dist/build/Cryptol/Parser/Lexer.hs 0000644 0000000 0000000 00001132455 12737220176 017766 0 ustar 00 0000000 0000000 {-# LANGUAGE CPP,MagicHash #-}
{-# LINE 1 "src/Cryptol/Parser/Lexer.x" #-}
-- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- At present Alex generates code with too many warnings.
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -w #-}
module Cryptol.Parser.Lexer
( primLexer, lexer, Layout(..)
, Token(..), TokenT(..)
, TokenV(..), TokenKW(..), TokenErr(..), TokenSym(..), TokenW(..)
, Located(..)
, Config(..)
, defaultConfig
) where
import Cryptol.Parser.Position
import Cryptol.Parser.LexerUtils
import Cryptol.Parser.Unlit(unLit)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as Text
#if __GLASGOW_HASKELL__ >= 603
#include "ghcconfig.h"
#elif defined(__GLASGOW_HASKELL__)
#include "config.h"
#endif
#if __GLASGOW_HASKELL__ >= 503
import Data.Array
import Data.Char (ord)
import Data.Array.Base (unsafeAt)
#else
import Array
import Char (ord)
#endif
#if __GLASGOW_HASKELL__ >= 503
import GHC.Exts
#else
import GlaExts
#endif
alex_base :: AlexAddr
alex_base = AlexA# "\x01\x00\x00\x00\x76\x00\x00\x00\x6c\x01\x00\x00\x62\x02\x00\x00\xd7\xff\xff\xff\x61\x03\x00\x00\x60\x03\x00\x00\xe0\x03\x00\x00\x60\x04\x00\x00\xe0\x04\x00\x00\x60\x05\x00\x00\xe0\x05\x00\x00\x60\x06\x00\x00\xe0\x06\x00\x00\x60\x07\x00\x00\xe0\x07\x00\x00\x60\x08\x00\x00\xe0\x08\x00\x00\x78\x00\x00\x00\x00\x00\x00\x00\x51\x09\x00\x00\x00\x00\x00\x00\xc2\x09\x00\x00\x00\x00\x00\x00\x33\x0a\x00\x00\x00\x00\x00\x00\xa4\x0a\x00\x00\x00\x00\x00\x00\x15\x0b\x00\x00\x00\x00\x00\x00\x86\x0b\x00\x00\xca\xff\xff\xff\x00\x00\x00\x00\xdd\x00\x00\x00\x00\x00\x00\x00\xc7\x0b\x00\x00\x00\x00\x00\x00\x08\x0c\x00\x00\x00\x00\x00\x00\x49\x0c\x00\x00\x00\x00\x00\x00\x8a\x0c\x00\x00\x00\x00\x00\x00\xcb\x0c\x00\x00\x5d\x00\x00\x00\xdf\xff\xff\xff\xd8\xff\xff\xff\xcb\x0d\x00\x00\x8b\x0d\x00\x00\x00\x00\x00\x00\x8b\x0e\x00\x00\x01\x0f\x00\x00\x4c\x0e\x00\x00\x00\x00\x00\x00\x01\x10\x00\x00\xc1\x0f\x00\x00\x00\x00\x00\x00\xc1\x10\x00\x00\x37\x11\x00\x00\x82\x10\x00\x00\x00\x00\x00\x00\x37\x12\x00\x00\xf7\x11\x00\x00\x00\x00\x00\x00\xf7\x12\x00\x00\xb7\x12\x00\x00\x00\x00\x00\x00\xed\xff\xff\xff\xb3\x13\x00\x00\xee\xff\xff\xff\xd6\x13\x00\x00\x00\x00\x00\x00\xf9\x13\x00\x00\x00\x00\x00\x00\xf8\x13\x00\x00\xef\xff\xff\xff\xdd\xff\xff\xff\x00\x00\x00\x00\xee\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9b\x00\x00\x00\xda\x16\x00\x00\xd9\x17\x00\x00\x33\x18\x00\x00\x73\x18\x00\x00\xed\x18\x00\x00\x67\x19\x00\x00\xe1\x19\x00\x00\x5b\x1a\x00\x00\xd5\x1a\x00\x00\x4f\x1b\x00\x00\xc9\x1b\x00\x00\x43\x1c\x00\x00\xbd\x1c\x00\x00\x37\x1d\x00\x00\xb1\x1d\x00\x00\x2b\x1e\x00\x00\xa5\x1e\x00\x00\x1f\x1f\x00\x00\x99\x1f\x00\x00\x13\x20\x00\x00\x8d\x20\x00\x00\x07\x21\x00\x00\x81\x21\x00\x00\xfb\x21\x00\x00\xea\xff\xff\xff\x79\x00\x00\x00\x94\x00\x00\x00\x3d\x02\x00\x00\x55\x02\x00\x00\x75\x22\x00\x00\xef\x22\x00\x00\x69\x23\x00\x00\xe3\x23\x00\x00\x5d\x24\x00\x00\xd7\x24\x00\x00\x51\x25\x00\x00\xcb\x25\x00\x00\x45\x26\x00\x00\xbf\x26\x00\x00\x39\x27\x00\x00\xb3\x27\x00\x00\x2d\x28\x00\x00\xa7\x28\x00\x00\x21\x29\x00\x00\x9b\x29\x00\x00\x15\x2a\x00\x00\x8f\x2a\x00\x00\x09\x2b\x00\x00\x83\x2b\x00\x00\xfd\x2b\x00\x00\x77\x2c\x00\x00\xf1\x2c\x00\x00\x6b\x2d\x00\x00\xe5\x2d\x00\x00\x5f\x2e\x00\x00\xd9\x2e\x00\x00\x53\x2f\x00\x00\xcd\x2f\x00\x00\x47\x30\x00\x00\xc1\x30\x00\x00\x3b\x31\x00\x00\xb5\x31\x00\x00\x2f\x32\x00\x00\xa9\x32\x00\x00\x23\x33\x00\x00\x9d\x33\x00\x00\x17\x34\x00\x00\x91\x34\x00\x00\x0b\x35\x00\x00\x85\x35\x00\x00\xff\x35\x00\x00\x79\x36\x00\x00\xf3\x36\x00\x00\x6d\x37\x00\x00\xe7\x37\x00\x00\x61\x38\x00\x00\xdb\x38\x00\x00\x55\x39\x00\x00\xcf\x39\x00\x00\x49\x3a\x00\x00\xc3\x3a\x00\x00\x3d\x3b\x00\x00\xb7\x3b\x00\x00\x31\x3c\x00\x00\xab\x3c\x00\x00\x25\x3d\x00\x00\x9f\x3d\x00\x00\x19\x3e\x00\x00\x93\x3e\x00\x00\x0d\x3f\x00\x00\x87\x3f\x00\x00\x01\x40\x00\x00\x7b\x40\x00\x00\xf5\x40\x00\x00\x6f\x41\x00\x00\xe9\x41\x00\x00\x63\x42\x00\x00\xbd\x42\x00\x00\xe0\x42\x00\x00\x03\x43\x00\x00\x26\x43\x00\x00\x49\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf1\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\xf2\xff\xff\xff\x00\x00\x00\x00\x6c\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8f\x43\x00\x00\xb2\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd5\x43\x00\x00\xf8\x43\x00\x00\x1b\x44\x00\x00\x3e\x44\x00\x00\x61\x44\x00\x00\x84\x44\x00\x00\xa7\x44\x00\x00\xca\x44\x00\x00\xed\x44\x00\x00\x10\x45\x00\x00"#
alex_table :: AlexAddr
alex_table = AlexA# "\x00\x00\x04\x00\x97\x00\x97\x00\x05\x00\xd6\x00\x49\x00\x43\x00\x6f\x00\x6f\x00\x56\x00\x56\x00\x56\x00\x56\x00\x56\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x45\x00\x45\x00\x04\x00\x6f\x00\x6f\x00\x47\x00\x47\x00\x49\x00\xc2\x00\xc3\x00\x56\x00\xd6\x00\xcd\x00\xd3\x00\xd6\x00\xd6\x00\xd6\x00\xce\x00\xc5\x00\xc6\x00\xd1\x00\xcf\x00\xbd\x00\xd0\x00\xbf\x00\xd8\x00\x72\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\xc0\x00\xbe\x00\xd5\x00\xbc\x00\xd6\x00\xd6\x00\xd6\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xc7\x00\xb8\x00\xc8\x00\xd7\x00\x74\x00\xc1\x00\x7e\x00\x97\x00\x97\x00\x97\x00\xa6\x00\x97\x00\x97\x00\x94\x00\xb6\x00\x97\x00\x97\x00\x84\x00\x92\x00\x96\x00\x97\x00\x99\x00\x97\x00\x97\x00\x97\x00\xa4\x00\x97\x00\x97\x00\x9d\x00\x67\x00\x97\x00\x97\x00\xc9\x00\xc4\x00\xca\x00\xd4\x00\x55\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x56\x00\x56\x00\x56\x00\x56\x00\x56\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x70\x00\x00\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x00\x00\x00\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x36\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x37\x00\x09\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x25\x00\x0f\x00\x17\x00\x17\x00\x17\x00\x18\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x30\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x40\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x41\x00\x06\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2b\x00\x0c\x00\x1d\x00\x1d\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x51\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x00\x00\x00\x00\x00\x00\x2e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x73\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3d\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3e\x00\x07\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x29\x00\x0d\x00\x1b\x00\x1b\x00\x1b\x00\x1c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\x58\x00\x00\x00\x59\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x00\x05\x00\x05\x00\x05\x00\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x00\x59\x00\x00\x00\x59\x00\x59\x00\x59\x00\x59\x00\x00\x00\x00\x00\x00\x00\x59\x00\x59\x00\x00\x00\x59\x00\x00\x00\x59\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\x59\x00\x59\x00\x59\x00\x59\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x00\x00\x59\x00\x00\x00\x59\x00\x58\x00\x00\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x00\x00\x59\x00\x00\x00\x59\x00\x40\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x3d\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x39\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x36\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x32\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x2f\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x06\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x07\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x08\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x09\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x0a\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x0b\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x21\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x25\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x29\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x34\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x37\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3b\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x32\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x34\x00\x0a\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x23\x00\x10\x00\x15\x00\x15\x00\x15\x00\x16\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x39\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3b\x00\x08\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x26\x00\x27\x00\x0e\x00\x19\x00\x19\x00\x19\x00\x1a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x46\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x48\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x46\x00\xd6\x00\xff\xff\xd6\x00\x00\x00\x48\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xff\xff\xd6\x00\xd6\x00\x00\x00\xd6\x00\xff\xff\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x40\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x41\x00\x06\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2b\x00\x0c\x00\x1d\x00\x1d\x00\x1d\x00\x1e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3d\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3f\x00\x3e\x00\x07\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x28\x00\x29\x00\x0d\x00\x1b\x00\x1b\x00\x1b\x00\x1c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x36\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x38\x00\x37\x00\x09\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x25\x00\x0f\x00\x17\x00\x17\x00\x17\x00\x18\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2f\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x31\x00\x30\x00\x0b\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x21\x00\x11\x00\x13\x00\x13\x00\x13\x00\x14\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\x58\x00\x58\x00\x00\x00\x00\x00\x00\x00\x58\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x58\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x00\x00\x00\x00\x00\x00\x59\x00\x58\x00\x00\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x58\x00\x59\x00\x00\x00\x59\x00\x59\x00\x59\x00\x59\x00\x00\x00\x00\x00\x00\x00\x59\x00\x59\x00\x00\x00\x59\x00\x00\x00\x59\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\x59\x00\x59\x00\x59\x00\x59\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\x00\x00\x59\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x59\x00\x00\x00\x59\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x6b\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x6c\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5a\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5d\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5e\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5f\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x60\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x61\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x62\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x64\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x65\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x69\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x6a\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x6e\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x75\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x7a\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb5\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb4\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb2\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb1\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\xb0\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xaf\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xae\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xad\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x82\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\xaa\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa9\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa8\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa7\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x8b\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa1\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x98\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa5\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x9f\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x9e\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x9b\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x9a\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x93\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x91\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x90\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x8f\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x8e\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x8d\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x8c\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x8a\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x89\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x88\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x95\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x87\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x86\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\xa0\x00\x97\x00\x97\x00\x85\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x83\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xab\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xac\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x81\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xa2\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x80\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x7f\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb3\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x7d\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x7c\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x7b\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x79\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x78\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x77\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x76\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xb7\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x6d\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x68\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x66\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x63\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5c\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x9c\x00\xa3\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x97\x00\x00\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x5b\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\x97\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xbb\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xcc\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xb9\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xba\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x44\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x57\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd2\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
alex_check :: AlexAddr
alex_check = AlexA# "\xff\xff\x2a\x00\x01\x00\x02\x00\x3a\x00\x04\x00\x2f\x00\x2a\x00\x30\x00\x31\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x2a\x00\x2a\x00\x2a\x00\x30\x00\x31\x00\x2f\x00\x2f\x00\x2f\x00\x2e\x00\x2e\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x0a\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x2f\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x0a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x22\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\xff\xff\x62\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x78\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x01\x00\x02\x00\xff\xff\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x0a\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\x0a\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x00\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x13\x00\x14\x00\x15\x00\x16\x00\x17\x00\x18\x00\x19\x00\x1a\x00\x1b\x00\x1c\x00\x1d\x00\x1e\x00\x1f\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x7f\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\x0a\x00\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\x2a\x00\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2f\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x80\x00\x81\x00\x82\x00\x83\x00\x84\x00\x85\x00\x86\x00\x87\x00\x88\x00\x89\x00\x8a\x00\x8b\x00\x8c\x00\x8d\x00\x8e\x00\x8f\x00\x90\x00\x91\x00\x92\x00\x93\x00\x94\x00\x95\x00\x96\x00\x97\x00\x98\x00\x99\x00\x9a\x00\x9b\x00\x9c\x00\x9d\x00\x9e\x00\x9f\x00\xa0\x00\xa1\x00\xa2\x00\xa3\x00\xa4\x00\xa5\x00\xa6\x00\xa7\x00\xa8\x00\xa9\x00\xaa\x00\xab\x00\xac\x00\xad\x00\xae\x00\xaf\x00\xb0\x00\xb1\x00\xb2\x00\xb3\x00\xb4\x00\xb5\x00\xb6\x00\xb7\x00\xb8\x00\xb9\x00\xba\x00\xbb\x00\xbc\x00\xbd\x00\xbe\x00\xbf\x00\xc0\x00\xc1\x00\xc2\x00\xc3\x00\xc4\x00\xc5\x00\xc6\x00\xc7\x00\xc8\x00\xc9\x00\xca\x00\xcb\x00\xcc\x00\xcd\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\xd2\x00\xd3\x00\xd4\x00\xd5\x00\xd6\x00\xd7\x00\xd8\x00\xd9\x00\xda\x00\xdb\x00\xdc\x00\xdd\x00\xde\x00\xdf\x00\xe0\x00\xe1\x00\xe2\x00\xe3\x00\xe4\x00\xe5\x00\xe6\x00\xe7\x00\xe8\x00\xe9\x00\xea\x00\xeb\x00\xec\x00\xed\x00\xee\x00\xef\x00\xf0\x00\xf1\x00\xf2\x00\xf3\x00\xf4\x00\xf5\x00\xf6\x00\xf7\x00\xf8\x00\xf9\x00\xfa\x00\xfb\x00\xfc\x00\xfd\x00\xfe\x00\xff\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x04\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x04\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
alex_deflt :: AlexAddr
alex_deflt = AlexA# "\xff\xff\x52\x00\x4a\x00\x4e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x20\x00\x22\x00\x22\x00\x24\x00\x24\x00\x26\x00\x26\x00\x28\x00\x28\x00\x2a\x00\x2a\x00\xff\xff\x31\x00\x31\x00\x35\x00\x35\x00\x38\x00\x38\x00\x3c\x00\x3c\x00\x3f\x00\x3f\x00\x42\x00\x42\x00\xff\xff\xff\xff\xff\xff\x57\x00\x57\x00\x57\x00\x54\x00\x54\x00\x54\x00\x54\x00\x52\x00\x52\x00\x52\x00\x50\x00\x50\x00\x50\x00\x50\x00\x4e\x00\x4e\x00\x4e\x00\x4a\x00\x4a\x00\x4a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4a\x00\xff\xff\xff\xff\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\xff\xff\xff\xff\xff\xff\xff\xff\x57\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
alex_accept = listArray (0::Int,216) [AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAccNone,AlexAcc (alex_action_0),AlexAcc (alex_action_0),AlexAcc (alex_action_1),AlexAcc (alex_action_1),AlexAcc (alex_action_2),AlexAcc (alex_action_2),AlexAcc (alex_action_3),AlexAcc (alex_action_4),AlexAcc (alex_action_5),AlexAcc (alex_action_6),AlexAcc (alex_action_7),AlexAcc (alex_action_8),AlexAcc (alex_action_9),AlexAcc (alex_action_10),AlexAcc (alex_action_11),AlexAcc (alex_action_12),AlexAcc (alex_action_13),AlexAcc (alex_action_14),AlexAcc (alex_action_15),AlexAcc (alex_action_16),AlexAcc (alex_action_17),AlexAcc (alex_action_18),AlexAcc (alex_action_19),AlexAcc (alex_action_20),AlexAcc (alex_action_21),AlexAcc (alex_action_22),AlexAcc (alex_action_23),AlexAcc (alex_action_24),AlexAcc (alex_action_25),AlexAcc (alex_action_26),AlexAcc (alex_action_27),AlexAcc (alex_action_28),AlexAcc (alex_action_29),AlexAcc (alex_action_30),AlexAcc (alex_action_31),AlexAcc (alex_action_32),AlexAcc (alex_action_33),AlexAcc (alex_action_34),AlexAcc (alex_action_35),AlexAcc (alex_action_36),AlexAcc (alex_action_38),AlexAcc (alex_action_39),AlexAcc (alex_action_40),AlexAcc (alex_action_41),AlexAcc (alex_action_42),AlexAcc (alex_action_43),AlexAcc (alex_action_44),AlexAcc (alex_action_44),AlexAcc (alex_action_45),AlexAcc (alex_action_46),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_47),AlexAcc (alex_action_48),AlexAcc (alex_action_49),AlexAcc (alex_action_50),AlexAcc (alex_action_51),AlexAcc (alex_action_52),AlexAcc (alex_action_53),AlexAcc (alex_action_54),AlexAcc (alex_action_55),AlexAcc (alex_action_56),AlexAcc (alex_action_57),AlexAcc (alex_action_58),AlexAcc (alex_action_59),AlexAcc (alex_action_60),AlexAcc (alex_action_61),AlexAcc (alex_action_62),AlexAcc (alex_action_63),AlexAcc (alex_action_64),AlexAcc (alex_action_65),AlexAcc (alex_action_66),AlexAcc (alex_action_67),AlexAcc (alex_action_68),AlexAcc (alex_action_69),AlexAcc (alex_action_70),AlexAcc (alex_action_71),AlexAcc (alex_action_72),AlexAcc (alex_action_73),AlexAcc (alex_action_74),AlexAcc (alex_action_75),AlexAcc (alex_action_76),AlexAcc (alex_action_77),AlexAcc (alex_action_77),AlexAcc (alex_action_77),AlexAcc (alex_action_77)]
{-# LINE 172 "src/Cryptol/Parser/Lexer.x" #-}
-- This code is here because it depends on `comment`, which is defined
-- in this file.
stateToInt :: LexS -> Int
stateToInt Normal = 0
stateToInt (InComment {}) = comment
stateToInt (InString {}) = string
stateToInt (InChar {}) = char
-- | Returns the tokens in the last position of the input that we processed.
-- White space is removed, and layout processing is done as requested.
-- This stream is fed to the parser.
lexer :: Config -> Text -> ([Located Token], Position)
lexer cfg cs = ( case cfgLayout cfg of
Layout -> layout cfg lexemes
NoLayout -> lexemes
, finalPos
)
where (lex0, finalPos) = primLexer cfg cs
lexemes = dropWhite lex0
-- | Returns the tokens and the last position of the input that we processed.
-- The tokens include whte space tokens.
primLexer :: Config -> Text -> ([Located Token], Position)
primLexer cfg cs = run inp Normal
where
inp = Inp { alexPos = start
, alexInputPrevChar = '\n'
, input = unLit (cfgPreProc cfg) cs }
singleR p = Range p p (cfgSource cfg)
eofR p = Range p' p' (cfgSource cfg)
where
p' = Position { line = line p + 1, col = 0 }
run i s =
case alexScan i (stateToInt s) of
AlexEOF ->
case s of
Normal -> ([ Located (eofR $ alexPos i) (Token EOF "end of file") ]
, alexPos i
)
InComment _ p _ _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedComment) "unterminated comment"
]
, alexPos i)
InString p _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedString) "unterminated string"
]
, alexPos i)
InChar p _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedChar) "unterminated character"
]
, alexPos i)
AlexError i' ->
let bad = Text.take 1 (input i)
in
( [ Located (Range (alexPos i) (alexPos i') (cfgSource cfg))
$ Token (Err LexicalError) bad ]
, alexPos i')
AlexSkip i' _ -> run i' s
AlexToken i' l act ->
let txt = Text.take (fromIntegral l) (input i)
(mtok,s') = act cfg (alexPos i) txt s
(rest,pos) = run i' $! s'
in case mtok of
Nothing -> (rest, pos)
Just t -> (t : rest, pos)
-- vim: ft=haskell
char,comment,string :: Int
char = 1
comment = 2
string = 3
alex_action_0 = startComment False
alex_action_1 = startComment True
alex_action_2 = startEndComment
alex_action_3 = endComent
alex_action_4 = addToComment
alex_action_5 = addToComment
alex_action_6 = addToComment
alex_action_7 = addToComment
alex_action_8 = addToString
alex_action_9 = endString
alex_action_10 = addToString
alex_action_11 = endString
alex_action_12 = addToChar
alex_action_13 = endChar
alex_action_14 = addToChar
alex_action_15 = endChar
alex_action_16 = emit $ White Space
alex_action_17 = emit $ White LineComment
alex_action_18 = mkQualIdent
alex_action_19 = mkQualOp
alex_action_20 = emit $ KW KW_else
alex_action_21 = emit $ KW KW_extern
alex_action_22 = emit $ KW KW_if
alex_action_23 = emit $ KW KW_private
alex_action_24 = emit $ KW KW_include
alex_action_25 = emit $ KW KW_module
alex_action_26 = emit $ KW KW_newtype
alex_action_27 = emit $ KW KW_pragma
alex_action_28 = emit $ KW KW_property
alex_action_29 = emit $ KW KW_then
alex_action_30 = emit $ KW KW_type
alex_action_31 = emit $ KW KW_where
alex_action_32 = emit $ KW KW_let
alex_action_33 = emit $ KW KW_x
alex_action_34 = emit $ KW KW_import
alex_action_35 = emit $ KW KW_as
alex_action_36 = emit $ KW KW_hiding
alex_action_37 = emit $ KW KW_newtype
alex_action_38 = emit $ KW KW_infixl
alex_action_39 = emit $ KW KW_infixr
alex_action_40 = emit $ KW KW_infix
alex_action_41 = emit $ KW KW_primitive
alex_action_42 = emitS (numToken 2 . Text.drop 2)
alex_action_43 = emitS (numToken 8 . Text.drop 2)
alex_action_44 = emitS (numToken 10 . Text.drop 0)
alex_action_45 = emitS (numToken 16 . Text.drop 2)
alex_action_46 = emit $ Sym Underscore
alex_action_47 = mkIdent
alex_action_48 = emit $ Sym Lambda
alex_action_49 = emit $ Sym ArrR
alex_action_50 = emit $ Sym ArrL
alex_action_51 = emit $ Sym FatArrR
alex_action_52 = emit $ Sym EqDef
alex_action_53 = emit $ Sym Comma
alex_action_54 = emit $ Sym Semi
alex_action_55 = emit $ Sym Dot
alex_action_56 = emit $ Sym Colon
alex_action_57 = emit $ Sym BackTick
alex_action_58 = emit $ Sym DotDot
alex_action_59 = emit $ Sym DotDotDot
alex_action_60 = emit $ Sym Bar
alex_action_61 = emit $ Sym ParenL
alex_action_62 = emit $ Sym ParenR
alex_action_63 = emit $ Sym BracketL
alex_action_64 = emit $ Sym BracketR
alex_action_65 = emit $ Sym CurlyL
alex_action_66 = emit $ Sym CurlyR
alex_action_67 = emit $ Sym TriL
alex_action_68 = emit $ Sym TriR
alex_action_69 = startString
alex_action_70 = startChar
alex_action_71 = emit (Op Plus )
alex_action_72 = emit (Op Minus)
alex_action_73 = emit (Op Mul )
alex_action_74 = emit (Op Exp )
alex_action_75 = emit (Op Hash )
alex_action_76 = emit (Op Complement)
alex_action_77 = emitS (Op . Other [])
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "" #-}
{-# LINE 18 "" #-}
{-# LINE 1 "/usr/local/Cellar/ghc/7.10.3b/lib/ghc-7.10.3/include/ghcversion.h" #-}
{-# LINE 19 "" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
-- -----------------------------------------------------------------------------
-- ALEX TEMPLATE
--
-- This code is in the PUBLIC DOMAIN; you may copy it freely and use
-- it for any purpose whatsoever.
-- -----------------------------------------------------------------------------
-- INTERNALS and main scanner engine
{-# LINE 21 "templates/GenericTemplate.hs" #-}
-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ > 706
#define GTE(n,m) (tagToEnum# (n >=# m))
#define EQ(n,m) (tagToEnum# (n ==# m))
#else
#define GTE(n,m) (n >=# m)
#define EQ(n,m) (n ==# m)
#endif
{-# LINE 51 "templates/GenericTemplate.hs" #-}
data AlexAddr = AlexA# Addr#
-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ < 503
uncheckedShiftL# = shiftL#
#endif
{-# INLINE alexIndexInt16OffAddr #-}
alexIndexInt16OffAddr (AlexA# arr) off =
#ifdef WORDS_BIGENDIAN
narrow16Int# i
where
i = word2Int# ((high `uncheckedShiftL#` 8#) `or#` low)
high = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
low = int2Word# (ord# (indexCharOffAddr# arr off'))
off' = off *# 2#
#else
indexInt16OffAddr# arr off
#endif
{-# INLINE alexIndexInt32OffAddr #-}
alexIndexInt32OffAddr (AlexA# arr) off =
#ifdef WORDS_BIGENDIAN
narrow32Int# i
where
i = word2Int# ((b3 `uncheckedShiftL#` 24#) `or#`
(b2 `uncheckedShiftL#` 16#) `or#`
(b1 `uncheckedShiftL#` 8#) `or#` b0)
b3 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 3#)))
b2 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 2#)))
b1 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
b0 = int2Word# (ord# (indexCharOffAddr# arr off'))
off' = off *# 4#
#else
indexInt32OffAddr# arr off
#endif
#if __GLASGOW_HASKELL__ < 503
quickIndex arr i = arr ! i
#else
-- GHC >= 503, unsafeAt is available from Data.Array.Base.
quickIndex = unsafeAt
#endif
-- -----------------------------------------------------------------------------
-- Main lexing routines
data AlexReturn a
= AlexEOF
| AlexError !AlexInput
| AlexSkip !AlexInput !Int
| AlexToken !AlexInput !Int a
-- alexScan :: AlexInput -> StartCode -> AlexReturn a
alexScan input (I# (sc))
= alexScanUser undefined input (I# (sc))
alexScanUser user input (I# (sc))
= case alex_scan_tkn user input 0# input sc AlexNone of
(AlexNone, input') ->
case alexGetByte input of
Nothing ->
AlexEOF
Just _ ->
AlexError input'
(AlexLastSkip input'' len, _) ->
AlexSkip input'' len
(AlexLastAcc k input''' len, _) ->
AlexToken input''' len k
-- Push the input through the DFA, remembering the most recent accepting
-- state it encountered.
alex_scan_tkn user orig_input len input s last_acc =
input `seq` -- strict in the input
let
new_acc = (check_accs (alex_accept `quickIndex` (I# (s))))
in
new_acc `seq`
case alexGetByte input of
Nothing -> (new_acc, input)
Just (c, new_input) ->
case fromIntegral c of { (I# (ord_c)) ->
let
base = alexIndexInt32OffAddr alex_base s
offset = (base +# ord_c)
check = alexIndexInt16OffAddr alex_check offset
new_s = if GTE(offset,0#) && EQ(check,ord_c)
then alexIndexInt16OffAddr alex_table offset
else alexIndexInt16OffAddr alex_deflt s
in
case new_s of
-1# -> (new_acc, input)
-- on an error, we want to keep the input *before* the
-- character that failed, not after.
_ -> alex_scan_tkn user orig_input (if c < 0x80 || c >= 0xC0 then (len +# 1#) else len)
-- note that the length is increased ONLY if this is the 1st byte in a char encoding)
new_input new_s new_acc
}
where
check_accs (AlexAccNone) = last_acc
check_accs (AlexAcc a ) = AlexLastAcc a input (I# (len))
check_accs (AlexAccSkip) = AlexLastSkip input (I# (len))
{-# LINE 198 "templates/GenericTemplate.hs" #-}
data AlexLastAcc a
= AlexNone
| AlexLastAcc a !AlexInput !Int
| AlexLastSkip !AlexInput !Int
instance Functor AlexLastAcc where
fmap f AlexNone = AlexNone
fmap f (AlexLastAcc x y z) = AlexLastAcc (f x) y z
fmap f (AlexLastSkip x y) = AlexLastSkip x y
data AlexAcc a user
= AlexAccNone
| AlexAcc a
| AlexAccSkip
{-# LINE 242 "templates/GenericTemplate.hs" #-}
-- used by wrappers
iUnbox (I# (i)) = i
cryptol-2.4.0/lib/ 0000755 0000000 0000000 00000000000 12737220176 012154 5 ustar 00 0000000 0000000 cryptol-2.4.0/lib/Cryptol.cry 0000644 0000000 0000000 00000021221 12737220176 014325 0 ustar 00 0000000 0000000 /*
* Copyright (c) 2013-2016 Galois, Inc.
* Distributed under the terms of the BSD3 license (see LICENSE file)
*/
module Cryptol where
/**
* The value corresponding to a numeric type.
*/
primitive demote : {val, bits} (fin val, fin bits, bits >= width val) => [bits]
infixr 10 ||
infixr 20 &&
infix 30 ==, ===, !=, !==
infix 40 >, >=, <, <=
infixl 50 ^
infixr 60 #
infixl 70 <<, <<<, >>, >>>
infixl 80 +, -
infixl 90 *, /
infixr 95 ^^
infixl 100 @, @@, !, !!
/**
* Add two values.
* * For words, addition uses modulo arithmetic.
* * Structured values are added element-wise.
*/
primitive (+) : {a} (Arith a) => a -> a -> a
/**
* For words, subtraction uses modulo arithmetic.
* Structured values are subtracted element-wise. Defined as:
* a - b = a + negate b
* See also: `negate'.
*/
primitive (-) : {a} (Arith a) => a -> a -> a
/**
* For words, multiplies two words, modulus 2^^a.
* Structured values are multiplied element-wise.
*/
primitive (*) : {a} (Arith a) => a -> a -> a
/**
* For words, divides two words, modulus 2^^a.
* Structured values are divided element-wise.
*/
primitive (/) : {a} (Arith a) => a -> a -> a
/**
* For words, takes the modulus of two words, modulus 2^^a.
* Over structured values, operates element-wise.
* Be careful, as this will often give unexpected results due to interaction of
* the two moduli.
*/
primitive (%) : {a} (Arith a) => a -> a -> a
/**
* For words, takes the exponent of two words, modulus 2^^a.
* Over structured values, operates element-wise.
* Be careful, due to its fast-growing nature, exponentiation is prone to
* interacting poorly with defaulting.
*/
primitive (^^) : {a} (Arith a) => a -> a -> a
/**
* Log base two.
*
* For words, computes the ceiling of log, base 2, of a number.
* Over structured values, operates element-wise.
*/
primitive lg2 : {a} (Arith a) => a -> a
type Bool = Bit
/**
* The constant True. Corresponds to the bit value 1.
*/
primitive True : Bit
/**
* The constant False. Corresponds to the bit value 0.
*/
primitive False : Bit
/**
* Returns the twos complement of its argument.
* Over structured values, operates element-wise.
* negate a = ~a + 1
*/
primitive negate : {a} (Arith a) => a -> a
/**
* Binary complement.
*/
primitive complement : {a} a -> a
/**
* Operator form of binary complement.
*/
(~) : {a} a -> a
(~) = complement
/**
* Less-than. Only works on comparable arguments.
*/
primitive (<) : {a} (Cmp a) => a -> a -> Bit
/**
* Greater-than of two comparable arguments.
*/
primitive (>) : {a} (Cmp a) => a -> a -> Bit
/**
* Less-than or equal of two comparable arguments.
*/
primitive (<=) : {a} (Cmp a) => a -> a -> Bit
/**
* Greater-than or equal of two comparable arguments.
*/
primitive (>=) : {a} (Cmp a) => a -> a -> Bit
/**
* Compares any two values of the same type for equality.
*/
primitive (==) : {a} (Cmp a) => a -> a -> Bit
/**
* Compares any two values of the same type for inequality.
*/
primitive (!=) : {a} (Cmp a) => a -> a -> Bit
/**
* Compare the outputs of two functions for equality
*/
(===) : {a,b} (Cmp b) => (a -> b) -> (a -> b) -> (a -> Bit)
f === g = \ x -> f x == g x
/**
* Compare the outputs of two functions for inequality
*/
(!==) : {a,b} (Cmp b) => (a -> b) -> (a -> b) -> (a -> Bit)
f !== g = \x -> f x != g x
/**
* Returns the smaller of two comparable arguments.
*/
min : {a} (Cmp a) => a -> a -> a
min x y = if x < y then x else y
/**
* Returns the greater of two comparable arguments.
*/
max : {a} (Cmp a) => a -> a -> a
max x y = if x > y then x else y
/**
* Logical `and' over bits. Extends element-wise over sequences, tuples.
*/
primitive (&&) : {a} a -> a -> a
/**
* Logical `or' over bits. Extends element-wise over sequences, tuples.
*/
primitive (||) : {a} a -> a -> a
/**
* Logical `exclusive or' over bits. Extends element-wise over sequences, tuples.
*/
primitive (^) : {a} a -> a -> a
/**
* Gives an arbitrary shaped value whose bits are all False.
* ~zero likewise gives an arbitrary shaped value whose bits are all True.
*/
primitive zero : {a} a
/**
* Left shift. The first argument is the sequence to shift, the second is the
* number of positions to shift by.
*/
primitive (<<) : {a, b, c} (fin b) => [a]c -> [b] -> [a]c
/**
* Right shift. The first argument is the sequence to shift, the second is the
* number of positions to shift by.
*/
primitive (>>) : {a, b, c} (fin b) => [a]c -> [b] -> [a]c
/**
* Left rotate. The first argument is the sequence to rotate, the second is the
* number of positions to rotate by.
*/
primitive (<<<) : {a, b, c} (fin a, fin b) => [a]c -> [b] -> [a]c
/**
* Right rotate. The first argument is the sequence to rotate, the second is
* the number of positions to rotate by.
*/
primitive (>>>) : {a, b, c} (fin a, fin b) => [a]c -> [b] -> [a]c
primitive (#) : {front, back, a} (fin front) => [front]a -> [back]a
-> [front + back] a
/**
* Split a sequence into a tuple of sequences.
*/
primitive splitAt : {front, back, a} (fin front) => [front + back]a
-> ([front]a, [back]a)
/**
* Joins sequences.
*/
primitive join : {parts, each, a} (fin each) => [parts][each]a
-> [parts * each]a
/**
* Splits a sequence into 'parts' groups with 'each' elements.
*/
primitive split : {parts, each, a} (fin each) => [parts * each]a
-> [parts][each]a
/**
* Reverses the elements in a sequence.
*/
primitive reverse : {a, b} (fin a) => [a]b -> [a]b
/**
* Transposes an [a][b] matrix into a [b][a] matrix.
*/
primitive transpose : {a, b, c} [a][b]c -> [b][a]c
/**
* Index operator. The first argument is a sequence. The second argument is
* the zero-based index of the element to select from the sequence.
*/
primitive (@) : {a, b, c} (fin c) => [a]b -> [c] -> b
/**
* Bulk index operator. The first argument is a sequence. The second argument
* is a sequence of the zero-based indices of the elements to select.
*/
primitive (@@) : {a, b, c, d} (fin d) => [a]b -> [c][d] -> [c]b
/**
* Reverse index operator. The first argument is a finite sequence. The second
* argument is the zero-based index of the element to select, starting from the
* end of the sequence.
*/
primitive (!) : {a, b, c} (fin a, fin c) => [a]b -> [c] -> b
/**
* Bulk reverse index operator. The first argument is a finite sequence. The
* second argument is a sequence of the zero-based indices of the elements to
z select, starting from the end of the sequence.
*/
primitive (!!) : {a, b, c, d} (fin a, fin d) => [a]b -> [c][d] -> [c]b
primitive fromThen : {first, next, bits, len}
( fin first, fin next, fin bits
, bits >= width first, bits >= width next
, lengthFromThen first next bits == len) => [len][bits]
primitive fromTo : {first, last, bits} (fin last, fin bits, last >= first,
bits >= width last) => [1 + (last - first)][bits]
primitive fromThenTo : {first, next, last, bits, len} (fin first, fin next,
fin last, fin bits, bits >= width first,
bits >= width next, bits >= width last,
lengthFromThenTo first next last == len) => [len][bits]
primitive infFrom : {bits} (fin bits) => [bits] -> [inf][bits]
primitive infFromThen : {bits} (fin bits) => [bits] -> [bits] -> [inf][bits]
primitive error : {at, len} (fin len) => [len][8] -> at
/**
* Performs multiplication of polynomials over GF(2).
*/
primitive pmult : {a, b} (fin a, fin b) => [a] -> [b] -> [max 1 (a + b) - 1]
/**
* Performs division of polynomials over GF(2).
*/
primitive pdiv : {a, b} (fin a, fin b) => [a] -> [b] -> [a]
/**
* Performs modulus of polynomials over GF(2).
*/
primitive pmod : {a, b} (fin a, fin b) => [a] -> [1 + b] -> [b]
/**
* Generates random values from a seed. When called with a function, currently
* generates a function that always returns zero.
*/
primitive random : {a} [256] -> a
type String n = [n][8]
type Word n = [n]
type Char = [8]
take : {front,back,elem} (fin front) => [front + back] elem -> [front] elem
take (x # _) = x
drop : {front,back,elem} (fin front) => [front + back] elem -> [back] elem
drop ((_ : [front] _) # y) = y
tail : {a, b} [1 + a]b -> [a]b
tail xs = drop`{1} xs
width : {bits,len,elem} (fin len, fin bits, bits >= width len) => [len] elem -> [bits]
width _ = `len
undefined : {a} a
undefined = error "undefined"
groupBy : {each,parts,elem} (fin each) =>
[parts * each] elem -> [parts][each]elem
groupBy = split`{parts=parts}
/**
* Define the base 2 logarithm function in terms of width
*/
type lg2 n = width (max n 1 - 1)
cryptol-2.4.0/lib/Cryptol/ 0000755 0000000 0000000 00000000000 12737220176 013610 5 ustar 00 0000000 0000000 cryptol-2.4.0/lib/Cryptol/Extras.cry 0000644 0000000 0000000 00000006052 12737220176 015600 0 ustar 00 0000000 0000000 /*
* Copyright (c) 2016 Galois, Inc.
* Distributed under the terms of the BSD3 license (see LICENSE file)
*
* This module contains definitions that we wish to eventually promote
* into the Prelude, but which currently cause typechecking of the
* Prelude to take too long (see #299)
*/
module Cryptol::Extras where
infixr 5 ==>
/**
* Logical implication
*/
(==>) : Bit -> Bit -> Bit
a ==> b = if a then b else True
/**
* Logical negation
*/
not : {a} a -> a
not a = ~ a
/**
* Conjunction
*/
and : {n} (fin n) => [n]Bit -> Bit
and xs = ~zero == xs
/**
* Disjunction
*/
or : {n} (fin n) => [n]Bit -> Bit
or xs = zero != xs
/**
* Conjunction after applying a predicate to all elements.
*/
all : {a,n} (fin n) => (a -> Bit) -> [n]a -> Bit
all f xs = and (map f xs)
/**
* Disjunction after applying a predicate to all elements.
*/
any : {a,n} (fin n) => (a -> Bit) -> [n]a -> Bit
any f xs = or (map f xs)
/**
* Map a function over an array.
*/
map : {a, b, n} (a -> b) -> [n]a -> [n]b
map f xs = [f x | x <- xs]
/**
* Functional left fold.
*
* foldl (+) 0 [1,2,3] = ((0 + 1) + 2) + 3
*/
foldl : {a, b, n} (fin n) => (a -> b -> a) -> a -> [n]b -> a
foldl f acc xs = ys ! 0
where ys = [acc] # [f a x | a <- ys | x <- xs]
/**
* Functional right fold.
*
* foldr (-) 0 [1,2,3] = 0 - (1 - (2 - 3))
*/
foldr : {a,b,n} (fin n) => (a -> b -> b) -> b -> [n]a -> b
foldr f acc xs = ys ! 0
where ys = [acc] # [f x a | a <- ys | x <- reverse xs]
/**
* Compute the sum of the words in the array.
*/
sum : {a,n} (fin n, Arith a) => [n]a -> a
sum xs = foldl (+) zero xs
/**
* Scan left is like a fold that emits the intermediate values.
*/
scanl : {b, a, n} (b -> a -> b) -> b -> [n]a -> [n+1]b
scanl f acc xs = ys
where
ys = [acc] # [f a x | a <- ys | x <- xs]
/**
* Scan right
*/
scanr : {a,b,n} (fin n) => (a -> b -> b) -> b -> [n]a -> [n+1]b
scanr f acc xs = reverse ys
where
ys = [acc] # [f x a | a <- ys | x <- reverse xs]
/**
* Zero extension
*/
extend : {total,n} (fin total, fin n, total >= n) => [n]Bit -> [total]Bit
extend n = zero # n
/**
* Signed extension. `extendSigned 0bwxyz : [8] == 0bwwwwwxyz`.
*/
extendSigned : {total,n} (fin total, fin n, n >= 1, total >= n+1) => [n]Bit -> [total]Bit
extendSigned xs = repeat (xs @ 0) # xs
/**
* Repeat a value.
*/
repeat : {n, a} a -> [n]a
repeat x = [ x | _ <- zero ]
/**
* `elem x xs` Returns true if x is equal to a value in xs.
*/
elem : {n,a} (fin n, Cmp a) => a -> [n]a -> Bit
elem a xs = any (\x -> x == a) xs
/**
* Create a list of tuples from two lists.
*/
zip : {a,b,n} [n]a -> [n]b -> [n](a,b)
zip xs ys = [(x,y) | x <- xs | y <- ys]
/**
* Create a list by applying the function to each pair of elements in the input.
* lists
*/
zipWith : {a,b,c,n} (a -> b -> c) -> [n]a -> [n]b -> [n]c
zipWith f xs ys = [f x y | x <- xs | y <- ys]
/**
* Transform a function into uncurried form.
*/
uncurry : {a,b,c} (a -> b -> c) -> (a,b) -> c
uncurry f = \(a,b) -> f a b
/**
* Transform a function into curried form.
*/
curry : {a,b,c} ((a, b) -> c) -> a -> b -> c
curry f = \a b -> f (a,b)
cryptol-2.4.0/src/ 0000755 0000000 0000000 00000000000 12737220176 012175 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/GitRev.hs 0000644 0000000 0000000 00000001040 12737220176 013724 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Include information about the current git status for use in error
-- messages and version info output
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
module GitRev (hash, branch, dirty) where
import Development.GitRev
hash :: String
hash = $(gitHash)
branch :: String
branch = $(gitBranch)
dirty :: Bool
dirty = $(gitDirty)
cryptol-2.4.0/src/Cryptol/ 0000755 0000000 0000000 00000000000 12737220176 013631 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Eval.hs 0000644 0000000 0000000 00000021213 12737220176 015053 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.Eval (
moduleEnv
, EvalEnv()
, emptyEnv
, evalExpr
, evalDecls
, EvalError(..)
, WithBase(..)
) where
import Cryptol.Eval.Error
import Cryptol.Eval.Env
import Cryptol.Eval.Type
import Cryptol.Eval.Value
import Cryptol.ModuleSystem.Name
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat (Nat')
import Cryptol.Utils.Panic (panic)
import Cryptol.Utils.PP
import Cryptol.Prims.Eval
import qualified Data.Map as Map
import Prelude ()
import Prelude.Compat
-- Expression Evaluation -------------------------------------------------------
moduleEnv :: Module -> EvalEnv -> EvalEnv
moduleEnv m env = evalDecls (mDecls m) (evalNewtypes (mNewtypes m) env)
evalExpr :: EvalEnv -> Expr -> Value
evalExpr env expr = case expr of
EList es ty -> VSeq (isTBit (evalValType env ty)) (map (evalExpr env) es)
ETuple es -> VTuple (map eval es)
ERec fields -> VRecord [ (f,eval e) | (f,e) <- fields ]
ESel e sel -> evalSel env e sel
EIf c t f | fromVBit (eval c) -> eval t
| otherwise -> eval f
EComp l h gs -> evalComp env (evalValType env l) h gs
EVar n -> case lookupVar n env of
Just val -> val
Nothing -> panic "[Eval] evalExpr"
["var `" ++ show (pp n) ++ "` is not defined"
, pretty (WithBase defaultPPOpts env)
]
ETAbs tv b -> case tpKind tv of
KType -> VPoly $ \ty -> evalExpr (bindType (tpVar tv) (Right ty) env) b
KNum -> VNumPoly $ \n -> evalExpr (bindType (tpVar tv) (Left n) env) b
k -> panic "[Eval] evalExpr" ["invalid kind on type abstraction", show k]
ETApp e ty -> case eval e of
VPoly f -> f (evalValType env ty)
VNumPoly f -> f (evalNumType env ty)
val -> panic "[Eval] evalExpr"
["expected a polymorphic value"
, show (ppV val), show e, show ty
]
EApp f x -> case eval f of
VFun f' -> f' (eval x)
it -> panic "[Eval] evalExpr" ["not a function", show (ppV it) ]
EAbs n _ty b -> VFun (\ val -> evalExpr (bindVar n val env) b )
-- XXX these will likely change once there is an evidence value
EProofAbs _ e -> evalExpr env e
EProofApp e -> evalExpr env e
ECast e _ty -> evalExpr env e
EWhere e ds -> evalExpr (evalDecls ds env) e
where
eval = evalExpr env
ppV = ppValue defaultPPOpts
-- Newtypes --------------------------------------------------------------------
evalNewtypes :: Map.Map Name Newtype -> EvalEnv -> EvalEnv
evalNewtypes nts env = Map.foldl (flip evalNewtype) env nts
-- | Introduce the constructor function for a newtype.
evalNewtype :: Newtype -> EvalEnv -> EvalEnv
evalNewtype nt = bindVar (ntName nt) (foldr tabs con (ntParams nt))
where
tabs _tp body = tlam (\ _ -> body)
con = VFun id
-- Declarations ----------------------------------------------------------------
evalDecls :: [DeclGroup] -> EvalEnv -> EvalEnv
evalDecls dgs env = foldl (flip evalDeclGroup) env dgs
evalDeclGroup :: DeclGroup -> EvalEnv -> EvalEnv
evalDeclGroup dg env = env'
where
-- the final environment is passed in for each declaration, to permit
-- recursive values.
env' = case dg of
Recursive ds -> foldr (evalDecl env') env ds
NonRecursive d -> evalDecl env d env
evalDecl :: ReadEnv -> Decl -> EvalEnv -> EvalEnv
evalDecl renv d =
bindVar (dName d) $
case dDefinition d of
DPrim -> evalPrim d
DExpr e -> evalExpr renv e
-- Selectors -------------------------------------------------------------------
evalSel :: ReadEnv -> Expr -> Selector -> Value
evalSel env e sel = case sel of
TupleSel n _ -> tupleSel n val
RecordSel n _ -> recordSel n val
ListSel ix _ -> fromSeq val !! ix
where
val = evalExpr env e
tupleSel n v =
case v of
VTuple vs -> vs !! n
VSeq False vs -> VSeq False [ tupleSel n v1 | v1 <- vs ]
VStream vs -> VStream [ tupleSel n v1 | v1 <- vs ]
VFun f -> VFun (\x -> tupleSel n (f x))
_ -> evalPanic "Cryptol.Eval.evalSel"
[ "Unexpected value in tuple selection"
, show (ppValue defaultPPOpts v) ]
recordSel n v =
case v of
VRecord {} -> lookupRecord n v
VSeq False vs -> VSeq False [ recordSel n v1 | v1 <- vs ]
VStream vs -> VStream [recordSel n v1 | v1 <- vs ]
VFun f -> VFun (\x -> recordSel n (f x))
_ -> evalPanic "Cryptol.Eval.evalSel"
[ "Unexpected value in record selection"
, show (ppValue defaultPPOpts v) ]
-- List Comprehension Environments ---------------------------------------------
-- | A variation of the ZipList type from Control.Applicative, with a
-- separate constructor for pure values. This datatype is used to
-- represent the list of values that each variable takes on within a
-- list comprehension. The @Zip@ constructor is for bindings that take
-- different values at different positions in the list, while the
-- @Pure@ constructor is for bindings originating outside the list
-- comprehension, which have the same value for all list positions.
data ZList a = Pure a | Zip [a]
getZList :: ZList a -> [a]
getZList (Pure x) = repeat x
getZList (Zip xs) = xs
instance Functor ZList where
fmap f (Pure x) = Pure (f x)
fmap f (Zip xs) = Zip (map f xs)
instance Applicative ZList where
pure x = Pure x
Pure f <*> Pure x = Pure (f x)
Pure f <*> Zip xs = Zip (map f xs)
Zip fs <*> Pure x = Zip (map ($ x) fs)
Zip fs <*> Zip xs = Zip (zipWith ($) fs xs)
-- | Evaluation environments for list comprehensions: Each variable
-- name is bound to a list of values, one for each element in the list
-- comprehension.
data ListEnv = ListEnv
{ leVars :: Map.Map Name (ZList Value)
, leTypes :: Map.Map TVar (Either Nat' TValue)
}
instance Monoid ListEnv where
mempty = ListEnv
{ leVars = Map.empty
, leTypes = Map.empty
}
mappend l r = ListEnv
{ leVars = Map.union (leVars l) (leVars r)
, leTypes = Map.union (leTypes l) (leTypes r)
}
toListEnv :: EvalEnv -> ListEnv
toListEnv e =
ListEnv
{ leVars = fmap Pure (envVars e)
, leTypes = envTypes e
}
-- | Take parallel slices of the list environment. If some names are
-- bound to longer lists of values (e.g. if they come from a different
-- parallel branch of a comprehension) then the last elements will be
-- dropped as the lists are zipped together.
zipListEnv :: ListEnv -> [EvalEnv]
zipListEnv (ListEnv vm tm) =
[ EvalEnv { envVars = v, envTypes = tm }
| v <- getZList (sequenceA vm) ]
bindVarList :: Name -> [Value] -> ListEnv -> ListEnv
bindVarList n vs lenv = lenv { leVars = Map.insert n (Zip vs) (leVars lenv) }
-- List Comprehensions ---------------------------------------------------------
-- | Evaluate a comprehension.
evalComp :: ReadEnv -> TValue -> Expr -> [[Match]] -> Value
evalComp env seqty body ms =
case isTSeq seqty of
Just (len, el) -> toSeq len el [ evalExpr e body | e <- envs ]
_ -> evalPanic "Cryptol.Eval" ["evalComp given a non sequence", show seqty]
-- XXX we could potentially print this as a number if the type was available.
where
-- generate a new environment for each iteration of each parallel branch
benvs :: [ListEnv]
benvs = map (branchEnvs (toListEnv env)) ms
-- join environments to produce environments at each step through the process.
envs :: [EvalEnv]
envs = zipListEnv (mconcat benvs)
-- | Turn a list of matches into the final environments for each iteration of
-- the branch.
branchEnvs :: ListEnv -> [Match] -> ListEnv
branchEnvs env matches = foldl evalMatch env matches
-- | Turn a match into the list of environments it represents.
evalMatch :: ListEnv -> Match -> ListEnv
evalMatch lenv m = case m of
-- many envs
From n _ty expr -> bindVarList n (concat vss) lenv'
where
vss = [ fromSeq (evalExpr env expr) | env <- zipListEnv lenv ]
stutter (Pure x) = Pure x
stutter (Zip xs) = Zip [ x | (x, vs) <- zip xs vss, _ <- vs ]
lenv' = lenv { leVars = fmap stutter (leVars lenv) }
-- XXX we don't currently evaluate these as though they could be recursive, as
-- they are typechecked that way; the read environment to evalExpr is the same
-- as the environment to bind a new name in.
Let d -> bindVarList (dName d) (map f (zipListEnv lenv)) lenv
where f env =
case dDefinition d of
DPrim -> evalPrim d
DExpr e -> evalExpr env e
cryptol-2.4.0/src/Cryptol/ModuleSystem.hs 0000644 0000000 0000000 00000007431 12737220176 016624 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE FlexibleContexts #-}
module Cryptol.ModuleSystem (
-- * Module System
ModuleEnv(..), initialModuleEnv
, DynamicEnv(..)
, ModuleError(..), ModuleWarning(..)
, ModuleCmd, ModuleRes
, findModule
, loadModuleByPath
, loadModule
, checkExpr
, evalExpr
, checkDecls
, evalDecls
, noPat
, focusedEnv
, getPrimMap
, renameVar
, renameType
-- * Interfaces
, Iface(..), IfaceDecls(..), genIface
, IfaceTySyn, IfaceDecl(..)
) where
import qualified Cryptol.Eval.Value as E
import Cryptol.ModuleSystem.Env
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Monad
import Cryptol.ModuleSystem.Name (Name,PrimMap)
import qualified Cryptol.ModuleSystem.Renamer as R
import qualified Cryptol.ModuleSystem.Base as Base
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.Name (PName)
import Cryptol.Parser.NoPat (RemovePatterns)
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.Utils.Ident as M
-- Public Interface ------------------------------------------------------------
type ModuleCmd a = ModuleEnv -> IO (ModuleRes a)
type ModuleRes a = (Either ModuleError (a,ModuleEnv), [ModuleWarning])
getPrimMap :: ModuleCmd PrimMap
getPrimMap me = runModuleM me Base.getPrimMap
-- | Find the file associated with a module name in the module search path.
findModule :: P.ModName -> ModuleCmd FilePath
findModule n env = runModuleM env (Base.findModule n)
-- | Load the module contained in the given file.
loadModuleByPath :: FilePath -> ModuleCmd T.Module
loadModuleByPath path env = runModuleM (resetModuleEnv env) $ do
-- unload the module if it already exists
unloadModule path
m <- Base.loadModuleByPath path
setFocusedModule (T.mName m)
return m
-- | Load the given parsed module.
loadModule :: FilePath -> P.Module PName -> ModuleCmd T.Module
loadModule path m env = runModuleM env $ do
-- unload the module if it already exists
unloadModule path
let n = P.thing (P.mName m)
m' <- loadingModule n (Base.loadModule path m)
setFocusedModule (T.mName m')
return m'
-- Extended Environments -------------------------------------------------------
-- These functions are particularly useful for interactive modes, as
-- they allow for expressions to be evaluated in an environment that
-- can extend dynamically outside of the context of a module.
-- | Check the type of an expression. Give back the renamed expression, the
-- core expression, and its type schema.
checkExpr :: P.Expr PName -> ModuleCmd (P.Expr Name,T.Expr,T.Schema)
checkExpr e env = runModuleM env (interactive (Base.checkExpr e))
-- | Evaluate an expression.
evalExpr :: T.Expr -> ModuleCmd E.Value
evalExpr e env = runModuleM env (interactive (Base.evalExpr e))
-- | Typecheck top-level declarations.
checkDecls :: [P.TopDecl PName] -> ModuleCmd (R.NamingEnv,[T.DeclGroup])
checkDecls ds env = runModuleM env
$ interactive
$ Base.checkDecls ds
-- | Evaluate declarations and add them to the extended environment.
evalDecls :: [T.DeclGroup] -> ModuleCmd ()
evalDecls dgs env = runModuleM env (interactive (Base.evalDecls dgs))
noPat :: RemovePatterns a => a -> ModuleCmd a
noPat a env = runModuleM env (interactive (Base.noPat a))
renameVar :: R.NamingEnv -> PName -> ModuleCmd Name
renameVar names n env = runModuleM env $ interactive $
Base.rename M.interactiveName names (R.renameVar n)
renameType :: R.NamingEnv -> PName -> ModuleCmd Name
renameType names n env = runModuleM env $ interactive $
Base.rename M.interactiveName names (R.renameType n)
cryptol-2.4.0/src/Cryptol/Parser.y 0000644 0000000 0000000 00000100111 12737220176 015251 0 ustar 00 0000000 0000000 {
-- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Trustworthy #-}
module Cryptol.Parser
( parseModule
, parseProgram, parseProgramWith
, parseExpr, parseExprWith
, parseDecl, parseDeclWith
, parseDecls, parseDeclsWith
, parseLetDecl, parseLetDeclWith
, parseRepl, parseReplWith
, parseSchema, parseSchemaWith
, parseModName, parseHelpName
, ParseError(..), ppError
, Layout(..)
, Config(..), defaultConfig
, guessPreProc, PreProc(..)
) where
import Control.Applicative as A
import Data.Maybe(fromMaybe)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import qualified Data.Text as ST
import Control.Monad(liftM2,msum)
import Cryptol.Prims.Syntax
import Cryptol.Parser.AST
import Cryptol.Parser.Position
import Cryptol.Parser.LexerUtils hiding (mkIdent)
import Cryptol.Parser.ParserUtils
import Cryptol.Parser.Unlit(PreProc(..), guessPreProc)
import Paths_cryptol
}
%token
NUM { $$@(Located _ (Token (Num {}) _))}
STRLIT { $$@(Located _ (Token (StrLit {}) _))}
CHARLIT { $$@(Located _ (Token (ChrLit {}) _))}
IDENT { $$@(Located _ (Token (Ident [] _) _))}
QIDENT { $$@(Located _ (Token Ident{} _))}
'include' { Located $$ (Token (KW KW_include) _)}
'import' { Located $$ (Token (KW KW_import) _)}
'as' { Located $$ (Token (KW KW_as) _)}
'hiding' { Located $$ (Token (KW KW_hiding) _)}
'private' { Located $$ (Token (KW KW_private) _)}
'property' { Located $$ (Token (KW KW_property) _)}
'infix' { Located $$ (Token (KW KW_infix) _)}
'infixl' { Located $$ (Token (KW KW_infixl) _)}
'infixr' { Located $$ (Token (KW KW_infixr) _)}
'type' { Located $$ (Token (KW KW_type ) _)}
'newtype' { Located $$ (Token (KW KW_newtype) _)}
'module' { Located $$ (Token (KW KW_module ) _)}
'where' { Located $$ (Token (KW KW_where ) _)}
'let' { Located $$ (Token (KW KW_let ) _)}
'if' { Located $$ (Token (KW KW_if ) _)}
'then' { Located $$ (Token (KW KW_then ) _)}
'else' { Located $$ (Token (KW KW_else ) _)}
'x' { Located $$ (Token (KW KW_x) _)}
'primitive' { Located $$ (Token (KW KW_primitive) _)}
'[' { Located $$ (Token (Sym BracketL) _)}
']' { Located $$ (Token (Sym BracketR) _)}
'<-' { Located $$ (Token (Sym ArrL ) _)}
'..' { Located $$ (Token (Sym DotDot ) _)}
'...' { Located $$ (Token (Sym DotDotDot) _)}
'|' { Located $$ (Token (Sym Bar ) _)}
'(' { Located $$ (Token (Sym ParenL ) _)}
')' { Located $$ (Token (Sym ParenR ) _)}
',' { Located $$ (Token (Sym Comma ) _)}
';' { Located $$ (Token (Sym Semi ) _)}
'.' { Located $$ (Token (Sym Dot ) _)}
'{' { Located $$ (Token (Sym CurlyL ) _)}
'}' { Located $$ (Token (Sym CurlyR ) _)}
'<|' { Located $$ (Token (Sym TriL ) _)}
'|>' { Located $$ (Token (Sym TriR ) _)}
'=' { Located $$ (Token (Sym EqDef ) _)}
'`' { Located $$ (Token (Sym BackTick) _)}
':' { Located $$ (Token (Sym Colon ) _)}
'->' { Located $$ (Token (Sym ArrR ) _)}
'=>' { Located $$ (Token (Sym FatArrR ) _)}
'\\' { Located $$ (Token (Sym Lambda ) _)}
'_' { Located $$ (Token (Sym Underscore ) _)}
'v{' { Located $$ (Token (Virt VCurlyL) _)}
'v}' { Located $$ (Token (Virt VCurlyR) _)}
'v;' { Located $$ (Token (Virt VSemi) _)}
'+' { Located $$ (Token (Op Plus) _)}
'*' { Located $$ (Token (Op Mul) _)}
'^^' { Located $$ (Token (Op Exp) _)}
'-' { Located $$ (Token (Op Minus) _)}
'~' { Located $$ (Token (Op Complement) _)}
'#' { Located $$ (Token (Op Hash) _)}
OP { $$@(Located _ (Token (Op (Other [] _)) _))}
QOP { $$@(Located _ (Token (Op Other{} ) _))}
DOC { $$@(Located _ (Token (White DocStr) _)) }
%name vmodule vmodule
%name program program
%name programLayout program_layout
%name expr expr
%name decl decl
%name decls decls
%name declsLayout decls_layout
%name letDecl let_decl
%name repl repl
%name schema schema
%name modName modName
%name helpName help_name
%tokentype { Located Token }
%monad { ParseM }
%lexer { lexerP } { Located _ (Token EOF _) }
{- If you add additional operators, please update the corresponding
tables in the pretty printer. -}
%nonassoc '=>'
%right '->'
%left 'where'
%nonassoc 'then' 'else'
%nonassoc ':'
%nonassoc '=='
%nonassoc '<=' '>='
%right '#'
%left '+' '-'
%left '*' '/' '%'
%right '^^'
%right NEG '~'
%left OP QOP
%%
vmodule :: { Module PName }
: 'module' modName 'where' 'v{' vmod_body 'v}'
{ let (is,ts) = $5 in Module $2 is ts }
| 'v{' vmod_body 'v}'
{ let { (is,ts) = $2
-- XXX make a location from is and ts
; modName = Located { srcRange = emptyRange
, thing = mkModName ["Main"]
}
} in Module modName is ts }
vmod_body :: { ([Located Import], [TopDecl PName]) }
: vimports 'v;' vtop_decls { (reverse $1, reverse $3) }
| vimports ';' vtop_decls { (reverse $1, reverse $3) }
| vimports { (reverse $1, []) }
| vtop_decls { ([], reverse $1) }
| {- empty -} { ([], []) }
vimports :: { [Located Import] }
: vimports 'v;' import { $3 : $1 }
| vimports ';' import { $3 : $1 }
| import { [$1] }
-- XXX replace rComb with uses of at
import :: { Located Import }
: 'import' modName mbAs mbImportSpec
{ Located { srcRange = rComb $1
$ fromMaybe (srcRange $2)
$ msum [ fmap srcRange $4
, fmap srcRange $3
]
, thing = Import
{ iModule = thing $2
, iAs = fmap thing $3
, iSpec = fmap thing $4
}
} }
mbAs :: { Maybe (Located ModName) }
: 'as' modName { Just $2 }
| {- empty -} { Nothing }
mbImportSpec :: { Maybe (Located ImportSpec) }
: mbHiding '(' name_list ')'{ Just Located
{ srcRange = case $3 of
{ [] -> emptyRange
; xs -> rCombs (map srcRange xs) }
, thing = $1 (reverse (map thing $3))
} }
| {- empty -} { Nothing }
name_list :: { [LIdent] }
: name_list ',' ident { $3 : $1 }
| ident { [$1] }
| {- empty -} { [] }
mbHiding :: { [Ident] -> ImportSpec }
: 'hiding' { Hiding }
| {- empty -} { Only }
program :: { Program PName }
: top_decls { Program (reverse $1) }
| {- empty -} { Program [] }
program_layout :: { Program PName }
: 'v{' vtop_decls 'v}' { Program (reverse $2) }
| 'v{''v}' { Program [] }
top_decls :: { [TopDecl PName] }
: top_decl ';' { $1 }
| top_decls top_decl ';' { $2 ++ $1 }
vtop_decls :: { [TopDecl PName] }
: vtop_decl { $1 }
| vtop_decls 'v;' vtop_decl { $3 ++ $1 }
| vtop_decls ';' vtop_decl { $3 ++ $1 }
vtop_decl :: { [TopDecl PName] }
: decl { [exportDecl Nothing Public $1] }
| doc decl { [exportDecl (Just $1) Public $2] }
| mbDoc 'include' STRLIT {% (return . Include) `fmap` fromStrLit $3 }
| mbDoc 'property' name apats '=' expr
{ [exportDecl $1 Public (mkProperty $3 $4 $6)] }
| mbDoc 'property' name '=' expr
{ [exportDecl $1 Public (mkProperty $3 [] $5)] }
| mbDoc newtype { [exportNewtype Public $2] }
| prim_bind { $1 }
| private_decls { $1 }
top_decl :: { [TopDecl PName] }
: decl { [Decl (TopLevel {tlExport = Public, tlValue = $1 })] }
| 'include' STRLIT {% (return . Include) `fmap` fromStrLit $2 }
| prim_bind { $1 }
private_decls :: { [TopDecl PName] }
: 'private' 'v{' vtop_decls 'v}'
{ changeExport Private (reverse $3) }
| doc 'private' 'v{' vtop_decls 'v}'
{ changeExport Private (reverse $4) }
prim_bind :: { [TopDecl PName] }
: mbDoc 'primitive' name ':' schema { mkPrimDecl $1 $3 $5 }
| mbDoc 'primitive' '(' op ')' ':' schema { mkPrimDecl $1 $4 $7 }
doc :: { Located String }
: DOC { mkDoc (fmap tokenText $1) }
mbDoc :: { Maybe (Located String) }
: doc { Just $1 }
| {- empty -} { Nothing }
decl :: { Decl PName }
: vars_comma ':' schema { at (head $1,$3) $ DSignature (reverse $1) $3 }
| ipat '=' expr { at ($1,$3) $ DPatBind $1 $3 }
| '(' op ')' '=' expr { at ($1,$5) $ DPatBind (PVar $2) $5 }
| var apats '=' expr { at ($1,$4) $
DBind $ Bind { bName = $1
, bParams = reverse $2
, bDef = at $4 (Located emptyRange (DExpr $4))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
} }
| apat other_op apat '=' expr
{ at ($1,$5) $
DBind $ Bind { bName = $2
, bParams = [$1,$3]
, bDef = at $5 (Located emptyRange (DExpr $5))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = True
, bFixity = Nothing
, bDoc = Nothing
} }
| 'type' name '=' type {% at ($1,$4) `fmap` mkTySyn $2 [] $4 }
| 'type' name tysyn_params '=' type
{% at ($1,$5) `fmap` mkTySyn $2 (reverse $3) $5 }
| 'infixl' NUM ops {% mkFixity LeftAssoc $2 (reverse $3) }
| 'infixr' NUM ops {% mkFixity RightAssoc $2 (reverse $3) }
| 'infix' NUM ops {% mkFixity NonAssoc $2 (reverse $3) }
let_decl :: { Decl PName }
: 'let' ipat '=' expr { at ($2,$4) $ DPatBind $2 $4 }
| 'let' name apats '=' expr { at ($2,$5) $
DBind $ Bind { bName = $2
, bParams = reverse $3
, bDef = at $5 (Located emptyRange (DExpr $5))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
} }
newtype :: { Newtype PName }
: 'newtype' qname '=' newtype_body
{ Newtype { nName = $2, nParams = [], nBody = $4 } }
| 'newtype' qname tysyn_params '=' newtype_body
{ Newtype { nName = $2, nParams = $3, nBody = $5 } }
newtype_body :: { [Named (Type PName)] }
: '{' '}' { [] }
| '{' field_types '}' { $2 }
vars_comma :: { [ LPName ] }
: var { [ $1] }
| vars_comma ',' var { $3 : $1 }
var :: { LPName }
: name { $1 }
| '(' op ')' { $2 }
apats :: { [Pattern PName] }
: apat { [$1] }
| apats1 apat { $2 : $1 }
apats1 :: { [Pattern PName] }
: apat { [$1] }
| apats1 apat { $2 : $1 }
decls :: { [Decl PName] }
: decl ';' { [$1] }
| decls decl ';' { $2 : $1 }
vdecls :: { [Decl PName] }
: decl { [$1] }
| vdecls 'v;' decl { $3 : $1 }
| vdecls ';' decl { $3 : $1 }
decls_layout :: { [Decl PName] }
: 'v{' vdecls 'v}' { $2 }
| 'v{' 'v}' { [] }
repl :: { ReplInput PName }
: expr { ExprInput $1 }
| let_decl { LetInput $1 }
--------------------------------------------------------------------------------
-- if a then b else c : [10]
expr :: { Expr PName }
: cexpr { $1 }
| expr 'where' '{' '}' { at ($1,$4) $ EWhere $1 [] }
| expr 'where' '{' decls '}' { at ($1,$5) $ EWhere $1 (reverse $4) }
| expr 'where' 'v{' 'v}' { at ($1,$2) $ EWhere $1 [] }
| expr 'where' 'v{' vdecls 'v}' { at ($1,$4) $ EWhere $1 (reverse $4) }
ifBranches :: { [(Expr PName, Expr PName)] }
: ifBranch { [$1] }
| ifBranches '|' ifBranch { $3 : $1 }
ifBranch :: { (Expr PName, Expr PName) }
: expr 'then' expr { ($1, $3) }
cexpr :: { Expr PName }
: sig_expr { $1 }
| 'if' ifBranches 'else' cexpr { at ($1,$4) $ mkIf (reverse $2) $4 }
| '\\' apats '->' cexpr { at ($1,$4) $ EFun (reverse $2) $4 }
sig_expr :: { Expr PName }
: iexpr { $1 }
| iexpr ':' type { at ($1,$3) $ ETyped $1 $3 }
iexpr :: { Expr PName }
: expr10 { $1 }
| iexpr qop expr10 { binOp $1 $2 $3 }
expr10 :: { Expr PName }
: aexprs { mkEApp $1 }
| '-' expr10 %prec NEG { at ($1,$2) $ EApp (at $1 (EVar (mkUnqual "negate"))) $2 }
| '~' expr10 { at ($1,$2) $ EApp (at $1 (EVar (mkUnqual "complement"))) $2 }
qop :: { LPName }
: op { $1 }
| QOP { let Token (Op (Other ns i)) _ = thing $1
in mkQual (mkModName ns) (mkInfix (T.toStrict i)) A.<$ $1 }
op :: { LPName }
: other_op { $1 }
-- special cases for operators that are re-used elsewhere
| '*' { Located $1 $ mkUnqual $ mkInfix "*" }
| '+' { Located $1 $ mkUnqual $ mkInfix "+" }
| '-' { Located $1 $ mkUnqual $ mkInfix "-" }
| '~' { Located $1 $ mkUnqual $ mkInfix "~" }
| '^^' { Located $1 $ mkUnqual $ mkInfix "^^" }
| '#' { Located $1 $ mkUnqual $ mkInfix "#" }
other_op :: { LPName }
: OP { let Token (Op (Other [] str)) _ = thing $1
in mkUnqual (mkInfix (T.toStrict str)) A.<$ $1 }
ops :: { [LPName] }
: op { [$1] }
| ops ',' op { $3 : $1 }
aexprs :: { [Expr PName] }
: aexpr { [$1] }
| aexprs aexpr { $2 : $1 }
aexpr :: { Expr PName }
: qname { at $1 $ EVar (thing $1) }
| NUM { at $1 $ numLit (tokenType (thing $1)) }
| STRLIT { at $1 $ ELit $ ECString $ getStr $1 }
| CHARLIT { at $1 $ ELit $ ECNum (getNum $1) CharLit }
| '(' expr ')' { at ($1,$3) $ EParens $2 }
| '(' tuple_exprs ')' { at ($1,$3) $ ETuple (reverse $2) }
| '(' ')' { at ($1,$2) $ ETuple [] }
| '{' '}' { at ($1,$2) $ ERecord [] }
| '{' field_exprs '}' { at ($1,$3) $ ERecord (reverse $2) }
| '[' ']' { at ($1,$2) $ EList [] }
| '[' list_expr ']' { at ($1,$3) $2 }
| '`' tick_ty { at ($1,$2) $ ETypeVal $2 }
| aexpr '.' selector { at ($1,$3) $ ESel $1 (thing $3) }
| '(' qop ')' { at ($1,$3) $ EVar $ thing $2 }
| '<|' '|>' {% mkPoly (rComb $1 $2) [] }
| '<|' poly_terms '|>' {% mkPoly (rComb $1 $3) $2 }
-- | error {%^ customError "expr" }
poly_terms :: { [(Bool, Integer)] }
: poly_term { [$1] }
| poly_terms '+' poly_term { $3 : $1 }
poly_term :: { (Bool, Integer) }
: NUM {% polyTerm (srcRange $1) (getNum $1) 0 }
| 'x' {% polyTerm $1 1 1 }
| 'x' '^^' NUM {% polyTerm (rComb $1 (srcRange $3))
1 (getNum $3) }
selector :: { Located Selector }
: ident { fmap (`RecordSel` Nothing) $1 }
| NUM {% mkTupleSel (srcRange $1) (getNum $1) }
tuple_exprs :: { [Expr PName] }
: expr ',' expr { [ $3, $1] }
| tuple_exprs ',' expr { $3 : $1 }
field_expr :: { Named (Expr PName) }
: ident '=' expr { Named { name = $1, value = $3 } }
| ident apats '=' expr { Named { name = $1, value = EFun (reverse $2) $4 } }
field_exprs :: { [Named (Expr PName)] }
: field_expr { [$1] }
| field_exprs ',' field_expr { $3 : $1 }
list_expr :: { Expr PName }
: expr '|' list_alts { EComp $1 (reverse $3) }
| expr { EList [$1] }
| tuple_exprs { EList (reverse $1) }
{- The `expr` in the four productions that follow should be `type`.
This, however, leads to ambiguity because the syntax for types and
expressions overlaps and we need more than 1 look-ahead to resolve what
is being parsed. For this reason, we use `expr` temporarily and
then convert it to the corresponding type in the AST. -}
| expr '..' {% eFromTo $2 $1 Nothing Nothing }
| expr '..' expr {% eFromTo $2 $1 Nothing (Just $3) }
| expr ',' expr '..' {% eFromTo $4 $1 (Just $3) Nothing }
| expr ',' expr '..' expr {% eFromTo $4 $1 (Just $3) (Just $5) }
| expr '...' { EInfFrom $1 Nothing }
| expr ',' expr '...' { EInfFrom $1 (Just $3) }
list_alts :: { [[Match PName]] }
: matches { [ reverse $1 ] }
| list_alts '|' matches { reverse $3 : $1 }
matches :: { [Match PName] }
: match { [$1] }
| matches ',' match { $3 : $1 }
match :: { Match PName }
: pat '<-' expr { Match $1 $3 }
--------------------------------------------------------------------------------
pat :: { Pattern PName }
: ipat ':' type { at ($1,$3) $ PTyped $1 $3 }
| ipat { $1 }
ipat
: ipat '#' ipat { at ($1,$3) $ PSplit $1 $3 }
| apat { $1 }
apat :: { Pattern PName }
: name { PVar $1 }
| '_' { at $1 $ PWild }
| '(' ')' { at ($1,$2) $ PTuple [] }
| '(' pat ')' { at ($1,$3) $2 }
| '(' tuple_pats ')' { at ($1,$3) $ PTuple (reverse $2) }
| '[' ']' { at ($1,$2) $ PList [] }
| '[' pat ']' { at ($1,$3) $ PList [$2] }
| '[' tuple_pats ']' { at ($1,$3) $ PList (reverse $2) }
| '{' '}' { at ($1,$2) $ PRecord [] }
| '{' field_pats '}' { at ($1,$3) $ PRecord (reverse $2) }
tuple_pats :: { [Pattern PName] }
: pat ',' pat { [$3, $1] }
| tuple_pats ',' pat { $3 : $1 }
field_pat :: { Named (Pattern PName) }
: ident '=' pat { Named { name = $1, value = $3 } }
field_pats :: { [Named (Pattern PName)] }
: field_pat { [$1] }
| field_pats ',' field_pat { $3 : $1 }
--------------------------------------------------------------------------------
schema :: { Schema PName }
: type { at $1 $ mkSchema [] [] $1 }
| schema_vars type { at ($1,$2) $ mkSchema (thing $1) [] $2 }
| schema_quals type { at ($1,$2) $ mkSchema [] (thing $1) $2 }
| schema_vars schema_quals type { at ($1,$3) $ mkSchema (thing $1)
(thing $2) $3 }
schema_vars :: { Located [TParam PName] }
: '{' '}' { Located (rComb $1 $2) [] }
| '{' schema_params '}' { Located (rComb $1 $3) (reverse $2) }
schema_quals :: { Located [Prop PName] }
: type '=>' {% fmap (\x -> at (x,$2) x) (mkProp $1) }
kind :: { Located Kind }
: '#' { Located $1 KNum }
| '*' { Located $1 KType }
schema_param :: { TParam PName }
: ident {% mkTParam $1 Nothing }
| ident ':' kind {% mkTParam (at ($1,$3) $1) (Just (thing $3)) }
schema_params :: { [TParam PName] }
: schema_param { [$1] }
| schema_params ',' schema_param { $3 : $1 }
tysyn_param :: { TParam PName }
: ident {% mkTParam $1 Nothing }
| '(' ident ':' kind ')' {% mkTParam (at ($1,$5) $2) (Just (thing $4)) }
tysyn_params :: { [TParam PName] }
: tysyn_param { [$1] }
| tysyn_params tysyn_param { $2 : $1 }
type :: { Type PName }
: app_type '->' type { at ($1,$3) $ TFun $1 $3 }
| type op app_type { at ($1,$3) $ TInfix $1 $2 defaultFixity $3 }
| app_type { $1 }
app_type :: { Type PName }
-- : 'lg2' atype { at ($1,$2) $ TApp TCLg2 [$2] }
-- | 'lengthFromThen' atype atype { at ($1,$3) $ TApp TCLenFromThen [$2,$3] }
-- | 'lengthFromThenTo' atype atype
-- atype { at ($1,$4) $ TApp TCLenFromThen [$2,$3,$4] }
-- | 'min' atype atype { at ($1,$3) $ TApp TCMin [$2,$3] }
-- | 'max' atype atype { at ($1,$3) $ TApp TCMax [$2,$3] }
: dimensions atype { at ($1,$2) $ foldr TSeq $2 (reverse (thing $1)) }
| qname atypes { at ($1,head $2)
$ TUser (thing $1) (reverse $2) }
| atype { $1 }
atype :: { Type PName }
: qname { at $1 $ TUser (thing $1) [] }
| NUM { at $1 $ TNum (getNum $1) }
| CHARLIT { at $1 $ TChar (toEnum $ fromInteger
$ getNum $1) }
| '[' type ']' { at ($1,$3) $ TSeq $2 TBit }
| '(' type ')' { at ($1,$3) $ TParens $2 }
| '(' ')' { at ($1,$2) $ TTuple [] }
| '(' tuple_types ')' { at ($1,$3) $ TTuple (reverse $2) }
| '{' '}' { at ($1,$2) $ TRecord [] }
| '{' field_types '}' { at ($1,$3) $ TRecord (reverse $2) }
| '_' { at $1 TWild }
atypes :: { [ Type PName ] }
: atype { [ $1 ] }
| atypes atype { $2 : $1 }
dimensions :: { Located [Type PName] }
: '[' type ']' { Located (rComb $1 $3) [ $2 ] }
| dimensions '[' type ']' { at ($1,$4) (fmap ($3 :) $1) }
tuple_types :: { [Type PName] }
: type ',' type { [ $3, $1] }
| tuple_types ',' type { $3 : $1 }
field_type :: { Named (Type PName) }
: ident ':' type { Named { name = $1, value = $3 } }
field_types :: { [Named (Type PName)] }
: field_type { [$1] }
| field_types ',' field_type { $3 : $1 }
ident :: { Located Ident }
: IDENT { let Token (Ident _ str) _ = thing $1
in $1 { thing = mkIdent (T.toStrict str) } }
| 'x' { Located { srcRange = $1, thing = mkIdent "x" }}
| 'private' { Located { srcRange = $1, thing = mkIdent "private" } }
| 'as' { Located { srcRange = $1, thing = mkIdent "as" } }
| 'hiding' { Located { srcRange = $1, thing = mkIdent "hiding" } }
name :: { LPName }
: ident { fmap mkUnqual $1 }
modName :: { Located ModName }
: ident { fmap identText $1 }
| QIDENT { let Token (Ident ns i) _ = thing $1
in mkModName (ns ++ [i]) A.<$ $1 }
qname :: { Located PName }
: name { $1 }
| QIDENT { let Token (Ident ns i) _ = thing $1
in mkQual (mkModName ns) (mkIdent (T.toStrict i)) A.<$ $1 }
help_name :: { Located PName }
: qname { $1 }
| qop { $1 }
| '(' qop ')' { $2 }
{- The types that can come after a back-tick: either a type demotion,
or an explicit type application. Explicit type applications are converted
to records, which cannot be demoted. -}
tick_ty :: { Type PName }
: qname { at $1 $ TUser (thing $1) [] }
| NUM { at $1 $ TNum (getNum $1) }
| '(' type ')' {% validDemotedType (rComb $1 $3) $2 }
| '{' '}' { at ($1,$2) (TRecord []) }
| '{' field_ty_vals '}' { at ($1,$3) (TRecord (reverse $2)) }
| '{' type '}' { anonRecord (getLoc ($1,$3)) [$2] }
| '{' tuple_types '}' { anonRecord (getLoc ($1,$3)) (reverse $2) }
-- This for explicit type applications (e.g., f ` { front = 3 })
field_ty_val :: { Named (Type PName) }
: ident '=' type { Named { name = $1, value = $3 } }
field_ty_vals :: { [Named (Type PName)] }
: field_ty_val { [$1] }
| field_ty_vals ',' field_ty_val { $3 : $1 }
{
parseModName :: String -> Maybe ModName
parseModName txt =
case parseString defaultConfig { cfgModuleScope = False } modName txt of
Right a -> Just (thing a)
Left _ -> Nothing
parseHelpName :: String -> Maybe PName
parseHelpName txt =
case parseString defaultConfig { cfgModuleScope = False } helpName txt of
Right a -> Just (thing a)
Left _ -> Nothing
addImplicitIncludes :: Config -> Program PName -> Program PName
addImplicitIncludes cfg (Program ds) =
Program $ map path (cfgAutoInclude cfg) ++ ds
where path p = Include Located { srcRange = rng, thing = p }
rng = Range { source = cfgSource cfg, from = start, to = start }
parseProgramWith :: Config -> Text -> Either ParseError (Program PName)
parseProgramWith cfg s = case res s of
Left err -> Left err
Right a -> Right (addImplicitIncludes cfg a)
where
res = parse cfg $ case cfgLayout cfg of
Layout -> programLayout
NoLayout -> program
parseModule :: Config -> Text -> Either ParseError (Module PName)
parseModule cfg = parse cfg { cfgModuleScope = True } vmodule
parseProgram :: Layout -> Text -> Either ParseError (Program PName)
parseProgram l = parseProgramWith defaultConfig { cfgLayout = l }
parseExprWith :: Config -> Text -> Either ParseError (Expr PName)
parseExprWith cfg = parse cfg { cfgModuleScope = False } expr
parseExpr :: Text -> Either ParseError (Expr PName)
parseExpr = parseExprWith defaultConfig
parseDeclWith :: Config -> Text -> Either ParseError (Decl PName)
parseDeclWith cfg = parse cfg { cfgModuleScope = False } decl
parseDecl :: Text -> Either ParseError (Decl PName)
parseDecl = parseDeclWith defaultConfig
parseDeclsWith :: Config -> Text -> Either ParseError [Decl PName]
parseDeclsWith cfg = parse cfg { cfgModuleScope = ms } decls'
where (ms, decls') = case cfgLayout cfg of
Layout -> (True, declsLayout)
NoLayout -> (False, decls)
parseDecls :: Text -> Either ParseError [Decl PName]
parseDecls = parseDeclsWith defaultConfig
parseLetDeclWith :: Config -> Text -> Either ParseError (Decl PName)
parseLetDeclWith cfg = parse cfg { cfgModuleScope = False } letDecl
parseLetDecl :: Text -> Either ParseError (Decl PName)
parseLetDecl = parseLetDeclWith defaultConfig
parseReplWith :: Config -> Text -> Either ParseError (ReplInput PName)
parseReplWith cfg = parse cfg { cfgModuleScope = False } repl
parseRepl :: Text -> Either ParseError (ReplInput PName)
parseRepl = parseReplWith defaultConfig
parseSchemaWith :: Config -> Text -> Either ParseError (Schema PName)
parseSchemaWith cfg = parse cfg { cfgModuleScope = False } schema
parseSchema :: Text -> Either ParseError (Schema PName)
parseSchema = parseSchemaWith defaultConfig
-- vim: ft=haskell
}
cryptol-2.4.0/src/Cryptol/Prelude.hs 0000644 0000000 0000000 00000001647 12737220176 015575 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Compile the prelude into the executable as a last resort
{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Cryptol.Prelude (writePreludeContents) where
import Cryptol.ModuleSystem.Monad
import System.Directory (getTemporaryDirectory)
import System.IO (hClose, hPutStr, openTempFile)
import Text.Heredoc (there)
preludeContents :: String
preludeContents = [there|lib/Cryptol.cry|]
-- | Write the contents of the Prelude to a temporary file so that
-- Cryptol can load the module.
writePreludeContents :: ModuleM FilePath
writePreludeContents = io $ do
tmpdir <- getTemporaryDirectory
(path, h) <- openTempFile tmpdir "Cryptol.cry"
hPutStr h preludeContents
hClose h
return path
cryptol-2.4.0/src/Cryptol/Symbolic.hs 0000644 0000000 0000000 00000046514 12737220176 015760 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ViewPatterns #-}
module Cryptol.Symbolic where
import Control.Monad (replicateM, when, zipWithM)
import Data.List (transpose, intercalate)
import qualified Data.Map as Map
import qualified Control.Exception as X
import qualified Data.SBV.Dynamic as SBV
import qualified Cryptol.ModuleSystem as M hiding (getPrimMap)
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.ModuleSystem.Base as M
import qualified Cryptol.ModuleSystem.Monad as M
import Cryptol.Symbolic.Prims
import Cryptol.Symbolic.Value
import qualified Cryptol.Eval.Value as Eval
import qualified Cryptol.Eval.Type (evalValType, evalNumType)
import qualified Cryptol.Eval.Env (EvalEnv(..))
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat (Nat'(..))
import Cryptol.Utils.Ident (Ident)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
import Prelude ()
import Prelude.Compat
-- External interface ----------------------------------------------------------
proverConfigs :: [(String, SBV.SMTConfig)]
proverConfigs =
[ ("cvc4" , SBV.cvc4 )
, ("yices" , SBV.yices )
, ("z3" , SBV.z3 )
, ("boolector", SBV.boolector)
, ("mathsat" , SBV.mathSAT )
, ("abc" , SBV.abc )
, ("offline" , SBV.defaultSMTCfg )
, ("any" , SBV.defaultSMTCfg )
]
proverNames :: [String]
proverNames = map fst proverConfigs
lookupProver :: String -> SBV.SMTConfig
lookupProver s =
case lookup s proverConfigs of
Just cfg -> cfg
-- should be caught by UI for setting prover user variable
Nothing -> panic "Cryptol.Symbolic" [ "invalid prover: " ++ s ]
type SatResult = [(Type, Expr, Eval.Value)]
data SatNum = AllSat | SomeSat Int
deriving (Show)
data QueryType = SatQuery SatNum | ProveQuery
deriving (Show)
data ProverCommand = ProverCommand {
pcQueryType :: QueryType
-- ^ The type of query to run
, pcProverName :: String
-- ^ Which prover to use (one of the strings in 'proverConfigs')
, pcVerbose :: Bool
-- ^ Verbosity flag passed to SBV
, pcExtraDecls :: [DeclGroup]
-- ^ Extra declarations to bring into scope for symbolic
-- simulation
, pcSmtFile :: Maybe FilePath
-- ^ Optionally output the SMTLIB query to a file
, pcExpr :: Expr
-- ^ The typechecked expression to evaluate
, pcSchema :: Schema
-- ^ The 'Schema' of @pcExpr@
}
-- | A prover result is either an error message, an empty result (eg
-- for the offline prover), a counterexample or a lazy list of
-- satisfying assignments.
data ProverResult = AllSatResult [SatResult] -- LAZY
| ThmResult [Type]
| EmptyResult
| ProverError String
satSMTResults :: SBV.SatResult -> [SBV.SMTResult]
satSMTResults (SBV.SatResult r) = [r]
allSatSMTResults :: SBV.AllSatResult -> [SBV.SMTResult]
allSatSMTResults (SBV.AllSatResult (_, rs)) = rs
thmSMTResults :: SBV.ThmResult -> [SBV.SMTResult]
thmSMTResults (SBV.ThmResult r) = [r]
proverError :: String -> M.ModuleCmd ProverResult
proverError msg modEnv = return (Right (ProverError msg, modEnv), [])
satProve :: ProverCommand -> M.ModuleCmd ProverResult
satProve ProverCommand {..} = protectStack proverError $ \modEnv ->
M.runModuleM modEnv $ do
let (isSat, mSatNum) = case pcQueryType of
ProveQuery -> (False, Nothing)
SatQuery sn -> case sn of
SomeSat n -> (True, Just n)
AllSat -> (True, Nothing)
let extDgs = allDeclGroups modEnv ++ pcExtraDecls
provers <-
case pcProverName of
"any" -> M.io SBV.sbvAvailableSolvers
_ -> return [(lookupProver pcProverName) { SBV.smtFile = pcSmtFile }]
let provers' = [ p { SBV.timing = pcVerbose, SBV.verbose = pcVerbose } | p <- provers ]
let tyFn = if isSat then existsFinType else forallFinType
let runProver fn tag e = do
case provers of
[prover] -> do
when pcVerbose $ M.io $
putStrLn $ "Trying proof with " ++ show prover
res <- M.io (fn prover e)
when pcVerbose $ M.io $
putStrLn $ "Got result from " ++ show prover
return (tag res)
_ ->
return [ SBV.ProofError
prover
[":sat with option prover=any requires option satNum=1"]
| prover <- provers ]
runProvers fn tag e = do
when pcVerbose $ M.io $
putStrLn $ "Trying proof with " ++
intercalate ", " (map show provers)
(firstProver, res) <- M.io (fn provers' e)
when pcVerbose $ M.io $
putStrLn $ "Got result from " ++ show firstProver
return (tag res)
let runFn = case pcQueryType of
ProveQuery -> runProvers SBV.proveWithAny thmSMTResults
SatQuery sn -> case sn of
SomeSat 1 -> runProvers SBV.satWithAny satSMTResults
_ -> runProver SBV.allSatWith allSatSMTResults
case predArgTypes pcSchema of
Left msg -> return (ProverError msg)
Right ts -> do when pcVerbose $ M.io $ putStrLn "Simulating..."
let env = evalDecls mempty extDgs
let v = evalExpr env pcExpr
prims <- M.getPrimMap
results' <- runFn $ do
args <- mapM tyFn ts
b <- return $! fromVBit (foldl fromVFun v args)
return b
let results = maybe results' (\n -> take n results') mSatNum
esatexprs <- case results of
-- allSat can return more than one as long as
-- they're satisfiable
(SBV.Satisfiable {} : _) -> do
tevss <- mapM mkTevs results
return $ AllSatResult tevss
where
mkTevs result =
let Right (_, cws) = SBV.getModel result
(vs, _) = parseValues ts cws
sattys = unFinType <$> ts
satexprs = zipWithM (Eval.toExpr prims) sattys vs
in case zip3 sattys <$> satexprs <*> pure vs of
Nothing ->
panic "Cryptol.Symbolic.sat"
[ "unable to make assignment into expression" ]
Just tevs -> return $ tevs
-- prove returns only one
[SBV.Unsatisfiable {}] ->
return $ ThmResult (unFinType <$> ts)
-- unsat returns empty
[] -> return $ ThmResult (unFinType <$> ts)
-- otherwise something is wrong
_ -> return $ ProverError (rshow results)
where rshow | isSat = show . SBV.AllSatResult . (boom,)
| otherwise = show . SBV.ThmResult . head
boom = panic "Cryptol.Symbolic.sat"
[ "attempted to evaluate bogus boolean for pretty-printing" ]
return esatexprs
satProveOffline :: ProverCommand -> M.ModuleCmd (Either String String)
satProveOffline ProverCommand {..} =
protectStack (\msg modEnv -> return (Right (Left msg, modEnv), [])) $ \modEnv -> do
let isSat = case pcQueryType of
ProveQuery -> False
SatQuery _ -> True
let extDgs = allDeclGroups modEnv ++ pcExtraDecls
let tyFn = if isSat then existsFinType else forallFinType
case predArgTypes pcSchema of
Left msg -> return (Right (Left msg, modEnv), [])
Right ts ->
do when pcVerbose $ putStrLn "Simulating..."
let env = evalDecls mempty extDgs
let v = evalExpr env pcExpr
smtlib <- SBV.compileToSMTLib SBV.SMTLib2 isSat $ do
args <- mapM tyFn ts
b <- return $! fromVBit (foldl fromVFun v args)
return b
return (Right (Right smtlib, modEnv), [])
protectStack :: (String -> M.ModuleCmd a)
-> M.ModuleCmd a
-> M.ModuleCmd a
protectStack mkErr cmd modEnv =
X.catchJust isOverflow (cmd modEnv) handler
where isOverflow X.StackOverflow = Just ()
isOverflow _ = Nothing
msg = "Symbolic evaluation failed to terminate."
handler () = mkErr msg modEnv
parseValues :: [FinType] -> [SBV.CW] -> ([Eval.Value], [SBV.CW])
parseValues [] cws = ([], cws)
parseValues (t : ts) cws = (v : vs, cws'')
where (v, cws') = parseValue t cws
(vs, cws'') = parseValues ts cws'
parseValue :: FinType -> [SBV.CW] -> (Eval.Value, [SBV.CW])
parseValue FTBit [] = panic "Cryptol.Symbolic.parseValue" [ "empty FTBit" ]
parseValue FTBit (cw : cws) = (Eval.VBit (SBV.cwToBool cw), cws)
parseValue (FTSeq 0 FTBit) cws = (Eval.VWord (Eval.BV 0 0), cws)
parseValue (FTSeq n FTBit) cws =
case SBV.genParse (SBV.KBounded False n) cws of
Just (x, cws') -> (Eval.VWord (Eval.BV (toInteger n) x), cws')
Nothing -> (Eval.VSeq True vs, cws')
where (vs, cws') = parseValues (replicate n FTBit) cws
parseValue (FTSeq n t) cws = (Eval.VSeq False vs, cws')
where (vs, cws') = parseValues (replicate n t) cws
parseValue (FTTuple ts) cws = (Eval.VTuple vs, cws')
where (vs, cws') = parseValues ts cws
parseValue (FTRecord fs) cws = (Eval.VRecord (zip ns vs), cws')
where (ns, ts) = unzip fs
(vs, cws') = parseValues ts cws
allDeclGroups :: M.ModuleEnv -> [DeclGroup]
allDeclGroups = concatMap mDecls . M.loadedModules
data FinType
= FTBit
| FTSeq Int FinType
| FTTuple [FinType]
| FTRecord [(Ident, FinType)]
numType :: Integer -> Maybe Int
numType n
| 0 <= n && n <= toInteger (maxBound :: Int) = Just (fromInteger n)
| otherwise = Nothing
finType :: TValue -> Maybe FinType
finType ty =
case ty of
TVBit -> Just FTBit
TVSeq n t -> FTSeq <$> numType n <*> finType t
TVTuple ts -> FTTuple <$> traverse finType ts
TVRec fields -> FTRecord <$> traverse (traverseSnd finType) fields
_ -> Nothing
unFinType :: FinType -> Type
unFinType fty =
case fty of
FTBit -> tBit
FTSeq l ety -> tSeq (tNum l) (unFinType ety)
FTTuple ftys -> tTuple (unFinType <$> ftys)
FTRecord fs -> tRec (zip fns tys)
where
fns = fst <$> fs
tys = unFinType . snd <$> fs
predArgTypes :: Schema -> Either String [FinType]
predArgTypes schema@(Forall ts ps ty)
| null ts && null ps =
case go (Cryptol.Eval.Type.evalValType mempty ty) of
Just fts -> Right fts
Nothing -> Left $ "Not a valid predicate type:\n" ++ show (pp schema)
| otherwise = Left $ "Not a monomorphic type:\n" ++ show (pp schema)
where
go :: TValue -> Maybe [FinType]
go TVBit = Just []
go (TVFun ty1 ty2) = (:) <$> finType ty1 <*> go ty2
go _ = Nothing
forallFinType :: FinType -> SBV.Symbolic Value
forallFinType ty =
case ty of
FTBit -> VBit <$> forallSBool_
FTSeq 0 FTBit -> return $ VWord (literalSWord 0 0)
FTSeq n FTBit -> VWord <$> (forallBV_ n)
FTSeq n t -> VSeq False <$> replicateM n (forallFinType t)
FTTuple ts -> VTuple <$> mapM forallFinType ts
FTRecord fs -> VRecord <$> mapM (traverseSnd forallFinType) fs
existsFinType :: FinType -> SBV.Symbolic Value
existsFinType ty =
case ty of
FTBit -> VBit <$> existsSBool_
FTSeq 0 FTBit -> return $ VWord (literalSWord 0 0)
FTSeq n FTBit -> VWord <$> existsBV_ n
FTSeq n t -> VSeq False <$> replicateM n (existsFinType t)
FTTuple ts -> VTuple <$> mapM existsFinType ts
FTRecord fs -> VRecord <$> mapM (traverseSnd existsFinType) fs
-- Simulation environment ------------------------------------------------------
data Env = Env
{ envVars :: Map.Map Name Value
, envTypes :: Map.Map TVar (Either Nat' TValue)
}
instance Monoid Env where
mempty = Env
{ envVars = Map.empty
, envTypes = Map.empty
}
mappend l r = Env
{ envVars = Map.union (envVars l) (envVars r)
, envTypes = Map.union (envTypes l) (envTypes r)
}
-- | Bind a variable in the evaluation environment.
bindVar :: (Name, Value) -> Env -> Env
bindVar (n, thunk) env = env { envVars = Map.insert n thunk (envVars env) }
-- | Lookup a variable in the environment.
lookupVar :: Name -> Env -> Maybe Value
lookupVar n env = Map.lookup n (envVars env)
-- | Bind a type variable of kind *.
bindType :: TVar -> (Either Nat' TValue) -> Env -> Env
bindType p ty env = env { envTypes = Map.insert p ty (envTypes env) }
-- | Lookup a type variable.
lookupType :: TVar -> Env -> Maybe (Either Nat' TValue)
lookupType p env = Map.lookup p (envTypes env)
-- Expressions -----------------------------------------------------------------
evalExpr :: Env -> Expr -> Value
evalExpr env expr =
case expr of
EList es ty -> VSeq (tIsBit ty) (map eval es)
ETuple es -> VTuple (map eval es)
ERec fields -> VRecord [ (f, eval e) | (f, e) <- fields ]
ESel e sel -> evalSel sel (eval e)
EIf b e1 e2 -> iteValue (fromVBit (eval b)) (eval e1) (eval e2)
EComp ty e mss -> evalComp env (evalValType env ty) e mss
EVar n -> case lookupVar n env of
Just x -> x
_ -> panic "Cryptol.Symbolic.evalExpr" [ "Variable " ++ show n ++ " not found" ]
-- TODO: how to deal with uninterpreted functions?
ETAbs tv e -> case tpKind tv of
KType -> VPoly $ \ty -> evalExpr (bindType (tpVar tv) (Right ty) env) e
KNum -> VNumPoly $ \n -> evalExpr (bindType (tpVar tv) (Left n) env) e
k -> panic "[Symbolic] evalExpr" ["invalid kind on type abstraction", show k]
ETApp e ty -> case eval e of
VPoly f -> f (evalValType env ty)
VNumPoly f -> f (evalNumType env ty)
_ -> panic "[Symbolic] evalExpr"
[ "expected a polymorphic value"
, show e, show ty
]
EApp e1 e2 -> fromVFun (eval e1) (eval e2)
EAbs n _ty e -> VFun $ \x -> evalExpr (bindVar (n, x) env) e
EProofAbs _prop e -> eval e
EProofApp e -> eval e
ECast e _ty -> eval e
EWhere e ds -> evalExpr (evalDecls env ds) e
where
eval e = evalExpr env e
evalValType :: Env -> Type -> TValue
evalValType env ty = Cryptol.Eval.Type.evalValType env' ty
where env' = Cryptol.Eval.Env.EvalEnv Map.empty (envTypes env)
evalNumType :: Env -> Type -> Nat'
evalNumType env ty = Cryptol.Eval.Type.evalNumType env' ty
where env' = Cryptol.Eval.Env.EvalEnv Map.empty (envTypes env)
evalSel :: Selector -> Value -> Value
evalSel sel v =
case sel of
TupleSel n _ ->
case v of
VTuple xs -> xs !! n -- 0-based indexing
VSeq b xs -> VSeq b (map (evalSel sel) xs)
VStream xs -> VStream (map (evalSel sel) xs)
VFun f -> VFun (\x -> evalSel sel (f x))
_ -> panic "Cryptol.Symbolic.evalSel" [ "Tuple selector applied to incompatible type" ]
RecordSel n _ ->
case v of
VRecord bs -> case lookup n bs of
Just x -> x
_ -> panic "Cryptol.Symbolic.evalSel" [ "Selector " ++ show n ++ " not found" ]
VSeq b xs -> VSeq b (map (evalSel sel) xs)
VStream xs -> VStream (map (evalSel sel) xs)
VFun f -> VFun (\x -> evalSel sel (f x))
_ -> panic "Cryptol.Symbolic.evalSel" [ "Record selector applied to non-record" ]
ListSel n _ -> case v of
VWord s -> VBit (SBV.svTestBit s i)
where i = SBV.intSizeOf s - 1 - n
_ -> fromSeq v !! n -- 0-based indexing
-- Declarations ----------------------------------------------------------------
evalDecls :: Env -> [DeclGroup] -> Env
evalDecls = foldl evalDeclGroup
evalDeclGroup :: Env -> DeclGroup -> Env
evalDeclGroup env dg =
case dg of
NonRecursive d -> bindVar (evalDecl env d) env
Recursive ds -> let env' = foldr bindVar env lazyBindings
bindings = map (evalDecl env') ds
lazyBindings = [ (qname, copyBySchema env (dSignature d) v)
| (d, (qname, v)) <- zip ds bindings ]
in env'
evalDecl :: Env -> Decl -> (Name, Value)
evalDecl env d = (dName d, body)
where
body = case dDefinition d of
DExpr e -> evalExpr env e
DPrim -> evalPrim d
-- | Make a copy of the given value, building the spine based only on
-- the type without forcing the value argument. This lets us avoid
-- strictness problems when evaluating recursive definitions.
copyBySchema :: Env -> Schema -> Value -> Value
copyBySchema env0 (Forall params _props ty) = go params env0
where
go [] env v = copyByType env (evalValType env ty) v
go (p : ps) env v =
case tpKind p of
KType -> VPoly (\t -> go ps (bindType (tpVar p) (Right t) env) (fromVPoly v t))
KNum -> VNumPoly (\t -> go ps (bindType (tpVar p) (Left t) env) (fromVNumPoly v t))
k -> panic "[Eval] copyBySchema" ["invalid kind on type abstraction", show k]
copyByType :: Env -> TValue -> Value -> Value
copyByType env ty v =
case ty of
TVBit -> VBit (fromVBit v)
TVSeq _ ety -> VSeq (isTBit ety) (fromSeq v)
TVStream _ -> VStream (fromSeq v)
TVFun _ bty -> VFun (\x -> copyByType env bty (fromVFun v x))
TVTuple tys -> VTuple (zipWith (copyByType env) tys (fromVTuple v))
TVRec fs -> VRecord [ (f, copyByType env t (lookupRecord f v)) | (f, t) <- fs ]
-- copyByType env ty v = logicUnary id id (evalValType env ty) v
-- List Comprehensions ---------------------------------------------------------
-- | Evaluate a comprehension.
evalComp :: Env -> TValue -> Expr -> [[Match]] -> Value
evalComp env seqty body ms =
case Eval.isTSeq seqty of
Just (len, el) -> toSeq len el [ evalExpr e body | e <- envs ]
Nothing -> evalPanic "Cryptol.Eval" ["evalComp given a non sequence", show seqty]
-- XXX we could potentially print this as a number if the type was available.
where
-- generate a new environment for each iteration of each parallel branch
benvs = map (branchEnvs env) ms
-- take parallel slices of each environment. when the length of the list
-- drops below the number of branches, one branch has terminated.
allBranches es = length es == length ms
slices = takeWhile allBranches (transpose benvs)
-- join environments to produce environments at each step through the process.
envs = map mconcat slices
-- | Turn a list of matches into the final environments for each iteration of
-- the branch.
branchEnvs :: Env -> [Match] -> [Env]
branchEnvs env matches =
case matches of
[] -> [env]
m : ms -> do env' <- evalMatch env m
branchEnvs env' ms
-- | Turn a match into the list of environments it represents.
evalMatch :: Env -> Match -> [Env]
evalMatch env m = case m of
From n _ty expr -> [ bindVar (n, v) env | v <- fromSeq (evalExpr env expr) ]
Let d -> [ bindVar (evalDecl env d) env ]
cryptol-2.4.0/src/Cryptol/TypeCheck.hs 0000644 0000000 0000000 00000007327 12737220176 016055 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE PatternGuards #-}
module Cryptol.TypeCheck
( tcModule
, tcExpr
, tcDecls
, InferInput(..)
, InferOutput(..)
, SolverConfig(..)
, NameSeeds
, nameSeeds
, Error(..)
, Warning(..)
, ppWarning
, ppError
) where
import Cryptol.ModuleSystem.Name (liftSupply,mkDeclared)
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.Position(Range,emptyRange)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Depends (FromDecl)
import Cryptol.TypeCheck.Monad
( runInferM
, InferInput(..)
, InferOutput(..)
, NameSeeds
, nameSeeds
, lookupVar
)
import Cryptol.TypeCheck.Infer (inferModule, inferBinds, inferDs)
import Cryptol.TypeCheck.InferTypes(Error(..),Warning(..),VarType(..), SolverConfig(..))
import Cryptol.TypeCheck.Solve(simplifyAllConstraints)
import Cryptol.Utils.Ident (packModName,packIdent)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
tcModule :: P.Module Name -> InferInput -> IO (InferOutput Module)
tcModule m inp = runInferM inp
$ do x <- inferModule m
simplifyAllConstraints
return x
tcExpr :: P.Expr Name -> InferInput -> IO (InferOutput (Expr,Schema))
tcExpr e0 inp = runInferM inp
$ do x <- go emptyRange e0
simplifyAllConstraints
return x
where
go loc expr =
case expr of
P.ELocated e loc' -> go loc' e
P.EVar x ->
do res <- lookupVar x
case res of
ExtVar s -> return (EVar x, s)
CurSCC e' t -> panic "Cryptol.TypeCheck.tcExpr"
[ "CurSCC outside binder checkig:"
, show e'
, show t
]
_ -> do fresh <- liftSupply (mkDeclared (packModName [""]) (packIdent "(expression)") Nothing loc)
res <- inferBinds True False
[ P.Bind
{ P.bName = P.Located { P.srcRange = loc, P.thing = fresh }
, P.bParams = []
, P.bDef = P.Located (inpRange inp) (P.DExpr expr)
, P.bPragmas = []
, P.bSignature = Nothing
, P.bMono = False
, P.bInfix = False
, P.bFixity = Nothing
, P.bDoc = Nothing
} ]
case res of
[d] | DExpr e <- dDefinition d -> return (e, dSignature d)
| otherwise ->
panic "Cryptol.TypeCheck.tcExpr"
[ "Expected an expression in definition"
, show d ]
_ -> panic "Cryptol.TypeCheck.tcExpr"
( "Multiple declarations when check expression:"
: map show res
)
tcDecls :: FromDecl d => [d] -> InferInput -> IO (InferOutput [DeclGroup])
tcDecls ds inp = runInferM inp $ inferDs ds $ \dgs -> do
simplifyAllConstraints
return dgs
ppWarning :: (Range,Warning) -> Doc
ppWarning (r,w) = text "[warning] at" <+> pp r <> colon $$ nest 2 (pp w)
ppError :: (Range,Error) -> Doc
ppError (r,w) = text "[error] at" <+> pp r <> colon $$ nest 2 (pp w)
cryptol-2.4.0/src/Cryptol/Version.hs 0000644 0000000 0000000 00000001117 12737220176 015612 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
module Cryptol.Version (
commitHash
, commitShortHash
, commitBranch
, commitDirty
, version
) where
import Paths_cryptol
import qualified GitRev
commitHash :: String
commitHash = GitRev.hash
commitShortHash :: String
commitShortHash = take 7 GitRev.hash
commitBranch :: String
commitBranch = GitRev.branch
commitDirty :: Bool
commitDirty = GitRev.dirty
cryptol-2.4.0/src/Cryptol/Eval/ 0000755 0000000 0000000 00000000000 12737220176 014520 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Eval/Arch.hs 0000644 0000000 0000000 00000001554 12737220176 015736 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Architecture-specific parts of the concrete evaluator go here.
{-# LANGUAGE CPP #-}
module Cryptol.Eval.Arch where
-- | This is the widest word we can have before gmp will fail to
-- allocate and bring down the whole program. According to
--
-- the sizes are 2^32-1 for 32-bit, and 2^37 for 64-bit, however
-- experiments show that it's somewhere under 2^37 at least on 64-bit
-- Mac OS X.
maxBigIntWidth :: Integer
#if i386_HOST_ARCH
maxBigIntWidth = 2^(32 :: Integer) - 0x1
#elif x86_64_HOST_ARCH
maxBigIntWidth = 2^(37 :: Integer) - 0x100
#else
#error unknown max width for gmp on this architecture
#endif
cryptol-2.4.0/src/Cryptol/Eval/Env.hs 0000644 0000000 0000000 00000003761 12737220176 015613 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.Eval.Env where
import Cryptol.Eval.Value
import Cryptol.ModuleSystem.Name
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat (Nat'(..))
import Cryptol.Utils.PP
import qualified Data.Map as Map
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- Evaluation Environment ------------------------------------------------------
type ReadEnv = EvalEnv
data EvalEnv = EvalEnv
{ envVars :: Map.Map Name Value
, envTypes :: Map.Map TVar (Either Nat' TValue)
} deriving (Generic, NFData)
instance Monoid EvalEnv where
mempty = EvalEnv
{ envVars = Map.empty
, envTypes = Map.empty
}
mappend l r = EvalEnv
{ envVars = Map.union (envVars l) (envVars r)
, envTypes = Map.union (envTypes l) (envTypes r)
}
instance PP (WithBase EvalEnv) where
ppPrec _ (WithBase opts env) = brackets (fsep (map bind (Map.toList (envVars env))))
where
bind (k,v) = pp k <+> text "->" <+> ppValue opts v
emptyEnv :: EvalEnv
emptyEnv = mempty
-- | Bind a variable in the evaluation environment.
bindVar :: Name -> Value -> EvalEnv -> EvalEnv
bindVar n val env = env { envVars = Map.insert n val (envVars env) }
-- | Lookup a variable in the environment.
lookupVar :: Name -> EvalEnv -> Maybe Value
lookupVar n env = Map.lookup n (envVars env)
-- | Bind a type variable of kind # or *.
bindType :: TVar -> Either Nat' TValue -> EvalEnv -> EvalEnv
bindType p ty env = env { envTypes = Map.insert p ty (envTypes env) }
-- | Lookup a type variable.
lookupType :: TVar -> EvalEnv -> Maybe (Either Nat' TValue)
lookupType p env = Map.lookup p (envTypes env)
cryptol-2.4.0/src/Cryptol/Eval/Error.hs 0000644 0000000 0000000 00000003555 12737220176 016155 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Cryptol.Eval.Error where
import Cryptol.Utils.Panic
import Cryptol.Utils.PP
import Cryptol.TypeCheck.AST(Type)
import Data.Typeable (Typeable)
import qualified Control.Exception as X
-- Errors ----------------------------------------------------------------------
-- | Panic from an Eval context.
evalPanic :: String -> [String] -> a
evalPanic cxt = panic ("[Eval] " ++ cxt)
data EvalError
= InvalidIndex Integer
| TypeCannotBeDemoted Type
| DivideByZero
| WordTooWide Integer
| UserError String
deriving (Typeable,Show)
instance PP EvalError where
ppPrec _ e = case e of
InvalidIndex i -> text "invalid sequence index:" <+> integer i
TypeCannotBeDemoted t -> text "type cannot be demoted:" <+> pp t
DivideByZero -> text "division by 0"
WordTooWide w ->
text "word too wide for memory:" <+> integer w <+> text "bits"
UserError x -> text "Run-time error:" <+> text x
instance X.Exception EvalError
-- | A sequencing operation has gotten an invalid index.
invalidIndex :: Integer -> a
invalidIndex i = X.throw (InvalidIndex i)
-- | For things like `(inf) or `(0-1)
typeCannotBeDemoted :: Type -> a
typeCannotBeDemoted t = X.throw (TypeCannotBeDemoted t)
-- | For division by 0.
divideByZero :: a
divideByZero = X.throw DivideByZero
-- | For when we know that a word is too wide and will exceed gmp's
-- limits (though words approaching this size will probably cause the
-- system to crash anyway due to lack of memory)
wordTooWide :: Integer -> a
wordTooWide w = X.throw (WordTooWide w)
-- | For `error`
cryUserError :: String -> a
cryUserError msg = X.throw (UserError msg)
cryptol-2.4.0/src/Cryptol/Eval/Type.hs 0000644 0000000 0000000 00000005634 12737220176 016005 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe, PatternGuards #-}
module Cryptol.Eval.Type (evalType, evalValType, evalNumType, evalTF) where
import Cryptol.Eval.Env
import Cryptol.Eval.Error
import Cryptol.Eval.Value (TValue(..), tvSeq)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat
import Data.Maybe(fromMaybe)
-- Type Evaluation -------------------------------------------------------------
-- | Evaluation for types (kind * or #).
evalType :: EvalEnv -> Type -> Either Nat' TValue
evalType env ty =
case ty of
TVar tv ->
case lookupType tv env of
Just v -> v
Nothing -> evalPanic "evalType" ["type variable not bound", show tv]
TUser _ _ ty' -> evalType env ty'
TRec fields -> Right $ TVRec [ (f, val t) | (f, t) <- fields ]
TCon (TC c) ts ->
case (c, ts) of
(TCBit, []) -> Right $ TVBit
(TCSeq, [n, t]) -> Right $ tvSeq (num n) (val t)
(TCFun, [a, b]) -> Right $ TVFun (val a) (val b)
(TCTuple _, _) -> Right $ TVTuple (map val ts)
(TCNum n, []) -> Left $ Nat n
(TCInf, []) -> Left $ Inf
-- FIXME: What about TCNewtype?
_ -> evalPanic "evalType" ["not a value type", show ty]
TCon (TF f) ts -> Left $ evalTF f (map num ts)
TCon (PC p) _ -> evalPanic "evalType" ["invalid predicate symbol", show p]
where
val = evalValType env
num = evalNumType env
-- | Evaluation for value types (kind *).
evalValType :: EvalEnv -> Type -> TValue
evalValType env ty =
case evalType env ty of
Left _ -> evalPanic "evalValType" ["expected value type, found numeric type"]
Right t -> t
evalNumType :: EvalEnv -> Type -> Nat'
evalNumType env ty =
case evalType env ty of
Left n -> n
Right _ -> evalPanic "evalValType" ["expected numeric type, found value type"]
-- | Reduce type functions, raising an exception for undefined values.
evalTF :: TFun -> [Nat'] -> Nat'
evalTF f vs
| TCAdd <- f, [x,y] <- vs = nAdd x y
| TCSub <- f, [x,y] <- vs = mb $ nSub x y
| TCMul <- f, [x,y] <- vs = nMul x y
| TCDiv <- f, [x,y] <- vs = mb $ nDiv x y
| TCMod <- f, [x,y] <- vs = mb $ nMod x y
| TCWidth <- f, [x] <- vs = nWidth x
| TCExp <- f, [x,y] <- vs = nExp x y
| TCMin <- f, [x,y] <- vs = nMin x y
| TCMax <- f, [x,y] <- vs = nMax x y
| TCLenFromThen <- f, [x,y,z] <- vs = mb $ nLenFromThen x y z
| TCLenFromThenTo <- f, [x,y,z] <- vs = mb $ nLenFromThenTo x y z
| otherwise = evalPanic "evalTF"
["Unexpected type function:", show ty]
where mb = fromMaybe (typeCannotBeDemoted ty)
ty = TCon (TF f) (map tNat' vs)
cryptol-2.4.0/src/Cryptol/Eval/Value.hs 0000644 0000000 0000000 00000031344 12737220176 016135 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.Eval.Value where
import qualified Cryptol.Eval.Arch as Arch
import Cryptol.Eval.Error
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat(Nat'(..))
import Cryptol.Utils.Ident (Ident,mkIdent)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
import Control.Monad (guard, zipWithM)
import Data.List(genericTake)
import Data.Bits (setBit,testBit,(.&.),shiftL)
import qualified Data.Text as T
import Numeric (showIntAtBase)
import GHC.Generics (Generic)
import Control.DeepSeq
-- Utilities -------------------------------------------------------------------
isTBit :: TValue -> Bool
isTBit TVBit = True
isTBit _ = False
isTSeq :: TValue -> Maybe (Nat', TValue)
isTSeq (TVSeq n t) = Just (Nat n, t)
isTSeq (TVStream t) = Just (Inf, t)
isTSeq _ = Nothing
isTFun :: TValue -> Maybe (TValue, TValue)
isTFun (TVFun t1 t2) = Just (t1, t2)
isTFun _ = Nothing
isTTuple :: TValue -> Maybe (Int,[TValue])
isTTuple (TVTuple ts) = Just (length ts, ts)
isTTuple _ = Nothing
isTRec :: TValue -> Maybe [(Ident, TValue)]
isTRec (TVRec fs) = Just fs
isTRec _ = Nothing
tvSeq :: Nat' -> TValue -> TValue
tvSeq (Nat n) t = TVSeq n t
tvSeq Inf t = TVStream t
finNat' :: Nat' -> Integer
finNat' n' =
case n' of
Nat x -> x
Inf -> panic "Cryptol.Eval.Value.finNat'" [ "Unexpected `inf`" ]
-- Values ----------------------------------------------------------------------
-- | width, value
-- Invariant: The value must be within the range 0 .. 2^width-1
data BV = BV !Integer !Integer deriving (Generic, NFData)
-- | Smart constructor for 'BV's that checks for the width limit
mkBv :: Integer -> Integer -> BV
mkBv w i = BV w (mask w i)
-- | Generic value type, parameterized by bit and word types.
data GenValue b w
= VRecord [(Ident, GenValue b w)] -- @ { .. } @
| VTuple [GenValue b w] -- @ ( .. ) @
| VBit b -- @ Bit @
| VSeq Bool [GenValue b w] -- @ [n]a @
-- The boolean parameter indicates whether or not
-- this is a sequence of bits.
| VWord w -- @ [n]Bit @
| VStream [GenValue b w] -- @ [inf]a @
| VFun (GenValue b w -> GenValue b w) -- functions
| VPoly (TValue -> GenValue b w) -- polymorphic values (kind *)
| VNumPoly (Nat' -> GenValue b w) -- polymorphic values (kind #)
deriving (Generic, NFData)
type Value = GenValue Bool BV
-- | An evaluated type of kind *.
-- These types do not contain type variables, type synonyms, or type functions.
data TValue
= TVBit
| TVSeq Integer TValue
| TVStream TValue -- ^ [inf]t
| TVTuple [TValue]
| TVRec [(Ident, TValue)]
| TVFun TValue TValue
deriving (Generic, NFData)
tValTy :: TValue -> Type
tValTy tv =
case tv of
TVBit -> tBit
TVSeq n t -> tSeq (tNum n) (tValTy t)
TVStream t -> tSeq tInf (tValTy t)
TVTuple ts -> tTuple (map tValTy ts)
TVRec fs -> tRec [ (f, tValTy t) | (f, t) <- fs ]
TVFun t1 t2 -> tFun (tValTy t1) (tValTy t2)
instance Show TValue where
showsPrec p v = showsPrec p (tValTy v)
-- Pretty Printing -------------------------------------------------------------
data PPOpts = PPOpts
{ useAscii :: Bool
, useBase :: Int
, useInfLength :: Int
}
defaultPPOpts :: PPOpts
defaultPPOpts = PPOpts { useAscii = False, useBase = 10, useInfLength = 5 }
ppValue :: PPOpts -> Value -> Doc
ppValue opts = loop
where
loop val = case val of
VRecord fs -> braces (sep (punctuate comma (map ppField fs)))
where
ppField (f,r) = pp f <+> char '=' <+> loop r
VTuple vals -> parens (sep (punctuate comma (map loop vals)))
VBit b | b -> text "True"
| otherwise -> text "False"
VSeq isWord vals
| isWord -> ppWord opts (fromVWord val)
| otherwise -> ppWordSeq vals
VWord (BV w i) -> ppWord opts (BV w i)
VStream vals -> brackets $ fsep
$ punctuate comma
( take (useInfLength opts) (map loop vals)
++ [text "..."]
)
VFun _ -> text ""
VPoly _ -> text ""
VNumPoly _ -> text ""
ppWordSeq ws =
case ws of
w : _
| Just l <- vWordLen w, asciiMode opts l ->
text $ show $ map (integerToChar . fromWord) ws
_ -> brackets (fsep (punctuate comma (map loop ws)))
asciiMode :: PPOpts -> Integer -> Bool
asciiMode opts width = useAscii opts && (width == 7 || width == 8)
integerToChar :: Integer -> Char
integerToChar = toEnum . fromInteger
data WithBase a = WithBase PPOpts a
deriving (Functor)
instance PP (WithBase Value) where
ppPrec _ (WithBase opts v) = ppValue opts v
ppWord :: PPOpts -> BV -> Doc
ppWord opts (BV width i)
| base > 36 = integer i -- not sure how to rule this out
| asciiMode opts width = text (show (toEnum (fromInteger i) :: Char))
| otherwise = prefix <> text value
where
base = useBase opts
padding bitsPerDigit = text (replicate padLen '0')
where
padLen | m > 0 = d + 1
| otherwise = d
(d,m) = (fromInteger width - (length value * bitsPerDigit))
`divMod` bitsPerDigit
prefix = case base of
2 -> text "0b" <> padding 1
8 -> text "0o" <> padding 3
10 -> empty
16 -> text "0x" <> padding 4
_ -> text "0" <> char '<' <> int base <> char '>'
value = showIntAtBase (toInteger base) (digits !!) i ""
digits = "0123456789abcdefghijklmnopqrstuvwxyz"
-- Big-endian Words ------------------------------------------------------------
class BitWord b w where
-- | NOTE this assumes that the sequence of bits is big-endian and finite, so the
-- first element of the list will be the most significant bit.
packWord :: [b] -> w
-- | NOTE this produces a list of bits that represent a big-endian word, so the
-- most significant bit is the first element of the list.
unpackWord :: w -> [b]
mask :: Integer -- ^ Bit-width
-> Integer -- ^ Value
-> Integer -- ^ Masked result
mask w i | w >= Arch.maxBigIntWidth = wordTooWide w
| otherwise = i .&. ((1 `shiftL` fromInteger w) - 1)
instance BitWord Bool BV where
packWord bits = BV (toInteger w) a
where
w = case length bits of
len | toInteger len >= Arch.maxBigIntWidth -> wordTooWide (toInteger len)
| otherwise -> len
a = foldl set 0 (zip [w - 1, w - 2 .. 0] bits)
set acc (n,b) | b = setBit acc n
| otherwise = acc
unpackWord (BV w a) = [ testBit a n | n <- [w' - 1, w' - 2 .. 0] ]
where
w' = fromInteger w
-- Value Constructors ----------------------------------------------------------
-- | Create a packed word of n bits.
word :: Integer -> Integer -> Value
word n i = VWord (mkBv n i)
lam :: (GenValue b w -> GenValue b w) -> GenValue b w
lam = VFun
-- | A type lambda that expects a @Type@ of kind *.
tlam :: (TValue -> GenValue b w) -> GenValue b w
tlam = VPoly
-- | A type lambda that expects a @Type@ of kind #.
nlam :: (Nat' -> GenValue b w) -> GenValue b w
nlam = VNumPoly
-- | Generate a stream.
toStream :: [GenValue b w] -> GenValue b w
toStream = VStream
toFinSeq :: TValue -> [GenValue b w] -> GenValue b w
toFinSeq elty = VSeq (isTBit elty)
-- | This is strict!
boolToWord :: [Bool] -> Value
boolToWord = VWord . packWord
-- | Construct either a finite sequence, or a stream. In the finite case,
-- record whether or not the elements were bits, to aid pretty-printing.
toSeq :: Nat' -> TValue -> [GenValue b w] -> GenValue b w
toSeq len elty vals = case len of
Nat n -> toFinSeq elty (genericTake n vals)
Inf -> toStream vals
-- | Construct one of:
-- * a word, when the sequence is finite and the elements are bits
-- * a sequence, when the sequence is finite but the elements aren't bits
-- * a stream, when the sequence is not finite
--
-- NOTE: do not use this constructor in the case where the thing may be a
-- finite, but recursive, sequence.
toPackedSeq :: Nat' -> TValue -> [Value] -> Value
toPackedSeq len elty vals = case len of
-- finite sequence, pack a word if the elements are bits.
Nat _ | isTBit elty -> boolToWord (map fromVBit vals)
| otherwise -> VSeq False vals
-- infinite sequence, construct a stream
Inf -> VStream vals
-- Value Destructors -----------------------------------------------------------
-- | Extract a bit value.
fromVBit :: GenValue b w -> b
fromVBit val = case val of
VBit b -> b
_ -> evalPanic "fromVBit" ["not a Bit"]
-- | Extract a sequence.
fromSeq :: BitWord b w => GenValue b w -> [GenValue b w]
fromSeq val = case val of
VSeq _ vs -> vs
VWord bv -> map VBit (unpackWord bv)
VStream vs -> vs
_ -> evalPanic "fromSeq" ["not a sequence"]
fromStr :: Value -> String
fromStr = map (toEnum . fromInteger . fromWord) . fromSeq
-- | Extract a packed word.
fromVWord :: BitWord b w => GenValue b w -> w
fromVWord val = case val of
VWord bv -> bv -- this should always mask
VSeq isWord bs | isWord -> packWord (map fromVBit bs)
_ -> evalPanic "fromVWord" ["not a word"]
vWordLen :: Value -> Maybe Integer
vWordLen val = case val of
VWord (BV w _) -> Just w
VSeq isWord bs | isWord -> Just (toInteger (length bs))
_ -> Nothing
-- | Turn a value into an integer represented by w bits.
fromWord :: Value -> Integer
fromWord val = a
where BV _ a = fromVWord val
-- | Extract a function from a value.
fromVFun :: GenValue b w -> (GenValue b w -> GenValue b w)
fromVFun val = case val of
VFun f -> f
_ -> evalPanic "fromVFun" ["not a function"]
-- | Extract a polymorphic function from a value.
fromVPoly :: GenValue b w -> (TValue -> GenValue b w)
fromVPoly val = case val of
VPoly f -> f
_ -> evalPanic "fromVPoly" ["not a polymorphic value"]
-- | Extract a polymorphic function from a value.
fromVNumPoly :: GenValue b w -> (Nat' -> GenValue b w)
fromVNumPoly val = case val of
VNumPoly f -> f
_ -> evalPanic "fromVNumPoly" ["not a polymorphic value"]
-- | Extract a tuple from a value.
fromVTuple :: GenValue b w -> [GenValue b w]
fromVTuple val = case val of
VTuple vs -> vs
_ -> evalPanic "fromVTuple" ["not a tuple"]
-- | Extract a record from a value.
fromVRecord :: GenValue b w -> [(Ident, GenValue b w)]
fromVRecord val = case val of
VRecord fs -> fs
_ -> evalPanic "fromVRecord" ["not a record"]
-- | Lookup a field in a record.
lookupRecord :: Ident -> GenValue b w -> GenValue b w
lookupRecord f rec = case lookup f (fromVRecord rec) of
Just val -> val
Nothing -> evalPanic "lookupRecord" ["malformed record"]
-- Value to Expression conversion ----------------------------------------------
-- | Given an expected type, returns an expression that evaluates to
-- this value, if we can determine it.
--
-- XXX: View patterns would probably clean up this definition a lot.
toExpr :: PrimMap -> Type -> Value -> Maybe Expr
toExpr prims = go
where
prim n = ePrim prims (mkIdent (T.pack n))
go ty val = case (ty, val) of
(TRec tfs, VRecord vfs) -> do
let fns = map fst vfs
guard (map fst tfs == fns)
fes <- zipWithM go (map snd tfs) (map snd vfs)
return $ ERec (zip fns fes)
(TCon (TC (TCTuple tl)) ts, VTuple tvs) -> do
guard (tl == (length tvs))
ETuple `fmap` zipWithM go ts tvs
(TCon (TC TCBit) [], VBit True ) -> return (prim "True")
(TCon (TC TCBit) [], VBit False) -> return (prim "False")
(TCon (TC TCSeq) [a,b], VSeq _ []) -> do
guard (a == tZero)
return $ EList [] b
(TCon (TC TCSeq) [a,b], VSeq _ svs) -> do
guard (a == tNum (length svs))
ses <- mapM (go b) svs
return $ EList ses b
(TCon (TC TCSeq) [a,(TCon (TC TCBit) [])], VWord (BV w v)) -> do
guard (a == tNum w)
return $ ETApp (ETApp (prim "demote") (tNum v)) (tNum w)
(_, VStream _) -> fail "cannot construct infinite expressions"
(_, VFun _) -> fail "cannot convert function values to expressions"
(_, VPoly _) -> fail "cannot convert polymorphic values to expressions"
_ -> panic "Cryptol.Eval.Value.toExpr"
["type mismatch:"
, pretty ty
, render (ppValue defaultPPOpts val)
]
cryptol-2.4.0/src/Cryptol/ModuleSystem/ 0000755 0000000 0000000 00000000000 12737220176 016263 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/ModuleSystem/Base.hs 0000644 0000000 0000000 00000034646 12737220176 017506 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
module Cryptol.ModuleSystem.Base where
import Cryptol.ModuleSystem.Env (DynamicEnv(..), deIfaceDecls)
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Monad
import Cryptol.ModuleSystem.Name (Name,liftSupply,PrimMap)
import Cryptol.ModuleSystem.Env (lookupModule, LoadedModule(..)
, meCoreLint, CoreLint(..))
import qualified Cryptol.Eval as E
import qualified Cryptol.Eval.Value as E
import qualified Cryptol.ModuleSystem.NamingEnv as R
import qualified Cryptol.ModuleSystem.Renamer as R
import qualified Cryptol.Parser as P
import qualified Cryptol.Parser.Unlit as P
import Cryptol.Parser.AST as P
import Cryptol.Parser.NoPat (RemovePatterns(removePatterns))
import Cryptol.Parser.NoInclude (removeIncludesModule)
import Cryptol.Parser.Position (HasLoc(..), Range, emptyRange)
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck.PP as T
import qualified Cryptol.TypeCheck.Sanity as TcSanity
import Cryptol.Utils.Ident (preludeName,interactiveName,unpackModName)
import Cryptol.Utils.PP (pretty)
import Cryptol.Utils.Panic (panic)
import Cryptol.Prelude (writePreludeContents)
import Cryptol.Transform.MonoValues (rewModule)
import Control.DeepSeq
import qualified Control.Exception as X
import Control.Monad (unless)
import Data.Function (on)
import Data.List (nubBy)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy.IO as T
import System.Directory (doesFileExist)
import System.FilePath ( addExtension
, isAbsolute
, joinPath
, (>)
, takeDirectory
, takeFileName
)
import qualified System.IO.Error as IOE
import qualified Data.Map as Map
import Prelude ()
import Prelude.Compat
-- Renaming --------------------------------------------------------------------
rename :: ModName -> R.NamingEnv -> R.RenameM a -> ModuleM a
rename modName env m = do
(res,ws) <- liftSupply $ \ supply ->
case R.runRenamer supply modName env m of
(Right (a,supply'),ws) -> ((Right a,ws),supply')
(Left errs,ws) -> ((Left errs,ws),supply)
renamerWarnings ws
case res of
Right r -> return r
Left errs -> renamerErrors errs
-- | Rename a module in the context of its imported modules.
renameModule :: P.Module PName
-> ModuleM (IfaceDecls,R.NamingEnv,P.Module Name)
renameModule m = do
(decls,menv) <- importIfaces (map thing (P.mImports m))
(declsEnv,rm) <- rename (thing (mName m)) menv (R.renameModule m)
return (decls,declsEnv,rm)
-- NoPat -----------------------------------------------------------------------
-- | Run the noPat pass.
noPat :: RemovePatterns a => a -> ModuleM a
noPat a = do
let (a',errs) = removePatterns a
unless (null errs) (noPatErrors errs)
return a'
-- Parsing ---------------------------------------------------------------------
parseModule :: FilePath -> ModuleM (P.Module PName)
parseModule path = do
e <- io $ X.try $ do
bytes <- T.readFile path
return $!! bytes
bytes <- case (e :: Either X.IOException Text) of
Right bytes -> return bytes
Left exn | IOE.isDoesNotExistError exn -> cantFindFile path
| otherwise -> otherIOError path exn
let cfg = P.defaultConfig
{ P.cfgSource = path
, P.cfgPreProc = P.guessPreProc path
}
case P.parseModule cfg bytes of
Right pm -> return pm
Left err -> moduleParseError path err
-- Modules ---------------------------------------------------------------------
-- | Load a module by its path.
loadModuleByPath :: FilePath -> ModuleM T.Module
loadModuleByPath path = withPrependedSearchPath [ takeDirectory path ] $ do
let fileName = takeFileName path
-- path' is the resolved, absolute path
path' <- findFile fileName
pm <- parseModule path'
let n = thing (P.mName pm)
-- Check whether this module name has already been loaded from a different file
env <- getModuleEnv
case lookupModule n env of
Nothing -> loadingModule n (loadModule path' pm)
Just lm
| path' == loaded -> return (lmModule lm)
| otherwise -> duplicateModuleName n path' loaded
where loaded = lmFilePath lm
-- | Load the module specified by an import.
loadImport :: Located P.Import -> ModuleM ()
loadImport li = do
let i = thing li
n = P.iModule i
alreadyLoaded <- isLoaded n
unless alreadyLoaded $
do path <- findModule n
pm <- parseModule path
loadingImport li $ do
-- make sure that this module is the one we expect
unless (n == thing (P.mName pm)) (moduleNameMismatch n (mName pm))
_ <- loadModule path pm
return ()
-- | Load dependencies, typecheck, and add to the eval environment.
loadModule :: FilePath -> P.Module PName -> ModuleM T.Module
loadModule path pm = do
let pm' = addPrelude pm
loadDeps pm'
-- XXX make it possible to configure output
io (putStrLn ("Loading module " ++ pretty (P.thing (P.mName pm'))))
tcm <- checkModule path pm'
-- extend the eval env
modifyEvalEnv (E.moduleEnv tcm)
loadedModule path tcm
return tcm
-- | Rewrite an import declaration to be of the form:
--
-- > import foo as foo [ [hiding] (a,b,c) ]
fullyQualified :: P.Import -> P.Import
fullyQualified i = i { iAs = Just (iModule i) }
-- | Find the interface referenced by an import, and generate the naming
-- environment that it describes.
importIface :: P.Import -> ModuleM (IfaceDecls,R.NamingEnv)
importIface imp =
do Iface { .. } <- getIface (T.iModule imp)
return (ifPublic, R.interpImport imp ifPublic)
-- | Load a series of interfaces, merging their public interfaces.
importIfaces :: [P.Import] -> ModuleM (IfaceDecls,R.NamingEnv)
importIfaces is = mconcat `fmap` mapM importIface is
moduleFile :: ModName -> String -> FilePath
moduleFile n = addExtension (joinPath (unpackModName n))
-- | Discover a module.
findModule :: ModName -> ModuleM FilePath
findModule n = do
paths <- getSearchPath
loop (possibleFiles paths)
where
loop paths = case paths of
path:rest -> do
b <- io (doesFileExist path)
if b then return path else loop rest
[] -> handleNotFound
handleNotFound =
case n of
m | m == preludeName -> writePreludeContents
_ -> moduleNotFound n =<< getSearchPath
-- generate all possible search paths
possibleFiles paths = do
path <- paths
ext <- P.knownExts
return (path > moduleFile n ext)
-- | Discover a file. This is distinct from 'findModule' in that we
-- assume we've already been given a particular file name.
findFile :: FilePath -> ModuleM FilePath
findFile path | isAbsolute path = do
-- No search path checking for absolute paths
b <- io (doesFileExist path)
if b then return path else cantFindFile path
findFile path = do
paths <- getSearchPath
loop (possibleFiles paths)
where
loop paths = case paths of
path':rest -> do
b <- io (doesFileExist path')
if b then return path' else loop rest
[] -> cantFindFile path
possibleFiles paths = map (> path) paths
-- | Add the prelude to the import list if it's not already mentioned.
addPrelude :: P.Module PName -> P.Module PName
addPrelude m
| preludeName == P.thing (P.mName m) = m
| preludeName `elem` importedMods = m
| otherwise = m { mImports = importPrelude : mImports m }
where
importedMods = map (P.iModule . P.thing) (P.mImports m)
importPrelude = P.Located
{ P.srcRange = emptyRange
, P.thing = P.Import
{ iModule = preludeName
, iAs = Nothing
, iSpec = Nothing
}
}
-- | Load the dependencies of a module into the environment.
loadDeps :: P.Module name -> ModuleM ()
loadDeps m
| null needed = return ()
| otherwise = mapM_ load needed
where
needed = nubBy ((==) `on` P.iModule . thing) (P.mImports m)
load mn = loadImport mn
-- Type Checking ---------------------------------------------------------------
-- | Load the local environment, which consists of the environment for the
-- currently opened module, shadowed by the dynamic environment.
getLocalEnv :: ModuleM (IfaceDecls,R.NamingEnv)
getLocalEnv =
do (decls,fNames,_) <- getFocusedEnv
denv <- getDynEnv
let dynDecls = deIfaceDecls denv
return (dynDecls `mappend` decls, deNames denv `R.shadowing` fNames)
-- | Typecheck a single expression, yielding a renamed parsed expression,
-- typechecked core expression, and a type schema.
checkExpr :: P.Expr PName -> ModuleM (P.Expr Name,T.Expr,T.Schema)
checkExpr e = do
(decls,names) <- getLocalEnv
-- run NoPat
npe <- noPat e
-- rename the expression with dynamic names shadowing the opened environment
re <- rename interactiveName names (R.rename npe)
-- merge the dynamic and opened environments for typechecking
prims <- getPrimMap
let act = TCAction { tcAction = T.tcExpr, tcLinter = exprLinter
, tcPrims = prims }
(te,s) <- typecheck act re decls
return (re,te,s)
-- | Typecheck a group of declarations.
--
-- INVARIANT: This assumes that NoPat has already been run on the declarations.
checkDecls :: [P.TopDecl PName] -> ModuleM (R.NamingEnv,[T.DeclGroup])
checkDecls ds = do
(decls,names) <- getLocalEnv
-- introduce names for the declarations before renaming them
declsEnv <- liftSupply (R.namingEnv' (map (R.InModule interactiveName) ds))
rds <- rename interactiveName (declsEnv `R.shadowing` names)
(traverse R.rename ds)
prims <- getPrimMap
let act = TCAction { tcAction = T.tcDecls, tcLinter = declsLinter
, tcPrims = prims }
ds' <- typecheck act rds decls
return (declsEnv,ds')
-- | Generate the primitive map. If the prelude is currently being loaded, this
-- should be generated directly from the naming environment given to the renamer
-- instead.
getPrimMap :: ModuleM PrimMap
getPrimMap =
do env <- getModuleEnv
case lookupModule preludeName env of
Just lm -> return (ifacePrimMap (lmInterface lm))
Nothing -> panic "Cryptol.ModuleSystem.Base.getPrimMap"
[ "Unable to find the prelude" ]
-- | Typecheck a module.
checkModule :: FilePath -> P.Module PName -> ModuleM T.Module
checkModule path m = do
-- remove includes first
e <- io (removeIncludesModule path m)
nim <- case e of
Right nim -> return nim
Left ierrs -> noIncludeErrors ierrs
-- remove pattern bindings
npm <- noPat nim
-- rename everything
(tcEnv,declsEnv,scm) <- renameModule npm
-- when generating the prim map for the typechecker, if we're checking the
-- prelude, we have to generate the map from the renaming environment, as we
-- don't have the interface yet.
prims <- if thing (mName m) == preludeName
then return (R.toPrimMap declsEnv)
else getPrimMap
-- typecheck
let act = TCAction { tcAction = T.tcModule
, tcLinter = moduleLinter (P.thing (P.mName m))
, tcPrims = prims }
tcm <- typecheck act scm tcEnv
liftSupply (`rewModule` tcm)
data TCLinter o = TCLinter
{ lintCheck ::
o -> T.InferInput -> Either TcSanity.Error [TcSanity.ProofObligation]
, lintModule :: Maybe P.ModName
}
exprLinter :: TCLinter (T.Expr, T.Schema)
exprLinter = TCLinter
{ lintCheck = \(e',s) i ->
case TcSanity.tcExpr (T.inpVars i) e' of
Left err -> Left err
Right (s1,os)
| TcSanity.same s s1 -> Right os
| otherwise -> Left (TcSanity.TypeMismatch s s1)
, lintModule = Nothing
}
declsLinter :: TCLinter [ T.DeclGroup ]
declsLinter = TCLinter
{ lintCheck = \ds' i -> case TcSanity.tcDecls (T.inpVars i) ds' of
Left err -> Left err
Right os -> Right os
, lintModule = Nothing
}
moduleLinter :: P.ModName -> TCLinter T.Module
moduleLinter m = TCLinter
{ lintCheck = \m' i -> case TcSanity.tcModule (T.inpVars i) m' of
Left err -> Left err
Right os -> Right os
, lintModule = Just m
}
data TCAction i o = TCAction
{ tcAction :: i -> T.InferInput -> IO (T.InferOutput o)
, tcLinter :: TCLinter o
, tcPrims :: PrimMap
}
typecheck :: (Show i, Show o, HasLoc i) => TCAction i o -> i -> IfaceDecls -> ModuleM o
typecheck act i env = do
let range = fromMaybe emptyRange (getLoc i)
input <- genInferInput range (tcPrims act) env
out <- io (tcAction act i input)
case out of
T.InferOK warns seeds supply' o ->
do setNameSeeds seeds
setSupply supply'
typeCheckWarnings warns
menv <- getModuleEnv
case meCoreLint menv of
NoCoreLint -> return ()
CoreLint -> case lintCheck (tcLinter act) o input of
Right as -> io $ mapM_ (print . T.pp) as
Left err -> panic "Core lint failed:" [show err]
return o
T.InferFailed warns errs ->
do typeCheckWarnings warns
typeCheckingFailed errs
-- | Generate input for the typechecker.
genInferInput :: Range -> PrimMap -> IfaceDecls -> ModuleM T.InferInput
genInferInput r prims env = do
seeds <- getNameSeeds
monoBinds <- getMonoBinds
cfg <- getSolverConfig
supply <- getSupply
-- TODO: include the environment needed by the module
return T.InferInput
{ T.inpRange = r
, T.inpVars = Map.map ifDeclSig (ifDecls env)
, T.inpTSyns = ifTySyns env
, T.inpNewtypes = ifNewtypes env
, T.inpNameSeeds = seeds
, T.inpMonoBinds = monoBinds
, T.inpSolverConfig = cfg
, T.inpSupply = supply
, T.inpPrimNames = prims
}
-- Evaluation ------------------------------------------------------------------
evalExpr :: T.Expr -> ModuleM E.Value
evalExpr e = do
env <- getEvalEnv
denv <- getDynEnv
return (E.evalExpr (env <> deEnv denv) e)
evalDecls :: [T.DeclGroup] -> ModuleM ()
evalDecls dgs = do
env <- getEvalEnv
denv <- getDynEnv
let env' = env <> deEnv denv
denv' = denv { deDecls = deDecls denv ++ dgs
, deEnv = E.evalDecls dgs env'
}
setDynEnv denv'
cryptol-2.4.0/src/Cryptol/ModuleSystem/Env.hs 0000644 0000000 0000000 00000021421 12737220176 017347 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.ModuleSystem.Env where
#ifndef RELOCATABLE
import Paths_cryptol (getDataDir)
#endif
import Cryptol.Eval (EvalEnv)
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Name (Supply,emptySupply)
import qualified Cryptol.ModuleSystem.NamingEnv as R
import Cryptol.Parser.AST
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.TypeCheck.AST as T
import Cryptol.Utils.PP (NameDisp)
import Control.Monad (guard)
import qualified Control.Exception as X
import Data.Foldable (fold)
import Data.Function (on)
import qualified Data.Map as Map
import Data.Monoid ((<>))
import System.Directory (getAppUserDataDirectory, getCurrentDirectory)
import System.Environment(getExecutablePath)
import System.FilePath ((>), normalise, joinPath, splitPath, takeDirectory)
import qualified Data.List as List
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- Module Environment ----------------------------------------------------------
data ModuleEnv = ModuleEnv
{ meLoadedModules :: LoadedModules
, meNameSeeds :: T.NameSeeds
, meEvalEnv :: EvalEnv
, meFocusedModule :: Maybe ModName
, meSearchPath :: [FilePath]
, meDynEnv :: DynamicEnv
, meMonoBinds :: !Bool
, meSolverConfig :: T.SolverConfig
, meCoreLint :: CoreLint
, meSupply :: !Supply
} deriving (Generic, NFData)
data CoreLint = NoCoreLint -- ^ Don't run core lint
| CoreLint -- ^ Run core lint
deriving (Generic, NFData)
resetModuleEnv :: ModuleEnv -> ModuleEnv
resetModuleEnv env = env
{ meLoadedModules = mempty
, meNameSeeds = T.nameSeeds
, meEvalEnv = mempty
, meFocusedModule = Nothing
, meDynEnv = mempty
}
initialModuleEnv :: IO ModuleEnv
initialModuleEnv = do
curDir <- getCurrentDirectory
#ifndef RELOCATABLE
dataDir <- getDataDir
#endif
binDir <- takeDirectory `fmap` getExecutablePath
let instDir = normalise . joinPath . init . splitPath $ binDir
-- looking up this directory can fail if no HOME is set, as in some
-- CI settings
let handle :: X.IOException -> IO String
handle _e = return ""
userDir <- X.catch (getAppUserDataDirectory "cryptol") handle
return ModuleEnv
{ meLoadedModules = mempty
, meNameSeeds = T.nameSeeds
, meEvalEnv = mempty
, meFocusedModule = Nothing
-- we search these in order, taking the first match
, meSearchPath = [ curDir
-- something like $HOME/.cryptol
, userDir
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
-- ../cryptol on win32
, instDir > "cryptol"
#else
-- ../share/cryptol on others
, instDir > "share" > "cryptol"
#endif
#ifndef RELOCATABLE
-- Cabal-defined data directory. Since this
-- is usually a global location like
-- /usr/local, search this one last in case
-- someone has multiple Cryptols
, dataDir
#endif
]
, meDynEnv = mempty
, meMonoBinds = True
, meSolverConfig = T.SolverConfig
{ T.solverPath = "z3"
, T.solverArgs = [ "-smt2", "-in" ]
, T.solverVerbose = 0
}
, meCoreLint = NoCoreLint
, meSupply = emptySupply
}
-- | Try to focus a loaded module in the module environment.
focusModule :: ModName -> ModuleEnv -> Maybe ModuleEnv
focusModule n me = do
guard (isLoaded n (meLoadedModules me))
return me { meFocusedModule = Just n }
-- | Get a list of all the loaded modules. Each module in the
-- resulting list depends only on other modules that precede it.
loadedModules :: ModuleEnv -> [T.Module]
loadedModules = map lmModule . getLoadedModules . meLoadedModules
-- | Produce an ifaceDecls that represents the focused environment of the module
-- system, as well as a 'NameDisp' for pretty-printing names according to the
-- imports.
--
-- XXX This could really do with some better error handling, just returning
-- mempty when one of the imports fails isn't really desirable.
focusedEnv :: ModuleEnv -> (IfaceDecls,R.NamingEnv,NameDisp)
focusedEnv me = fold $
do fm <- meFocusedModule me
lm <- lookupModule fm me
deps <- mapM loadImport (T.mImports (lmModule lm))
let (ifaces,names) = unzip deps
Iface { .. } = lmInterface lm
localDecls = ifPublic `mappend` ifPrivate
localNames = R.unqualifiedEnv localDecls
namingEnv = localNames `R.shadowing` mconcat names
return (mconcat (localDecls:ifaces), namingEnv, R.toNameDisp namingEnv)
where
loadImport imp =
do lm <- lookupModule (iModule imp) me
let decls = ifPublic (lmInterface lm)
return (decls,R.interpImport imp decls)
-- | The unqualified declarations and name environment for the dynamic
-- environment.
dynamicEnv :: ModuleEnv -> (IfaceDecls,R.NamingEnv,NameDisp)
dynamicEnv me = (decls,names,R.toNameDisp names)
where
decls = deIfaceDecls (meDynEnv me)
names = R.unqualifiedEnv decls
-- | Retrieve all 'IfaceDecls' referenced by a module, as well as all of its
-- public and private declarations, checking expressions
qualifiedEnv :: ModuleEnv -> IfaceDecls
qualifiedEnv me = fold $
do fm <- meFocusedModule me
lm <- lookupModule fm me
deps <- mapM loadImport (T.mImports (lmModule lm))
let Iface { .. } = lmInterface lm
return (mconcat (ifPublic : ifPrivate : deps))
where
loadImport imp =
do lm <- lookupModule (iModule imp) me
return (ifPublic (lmInterface lm))
-- Loaded Modules --------------------------------------------------------------
newtype LoadedModules = LoadedModules
{ getLoadedModules :: [LoadedModule]
} deriving (Show, Generic, NFData)
-- ^ Invariant: All the dependencies of any module `m` must precede `m` in the list.
instance Monoid LoadedModules where
mempty = LoadedModules []
mappend l r = LoadedModules
$ List.unionBy ((==) `on` lmName) (getLoadedModules l) (getLoadedModules r)
data LoadedModule = LoadedModule
{ lmName :: ModName
, lmFilePath :: FilePath
, lmInterface :: Iface
, lmModule :: T.Module
} deriving (Show, Generic, NFData)
isLoaded :: ModName -> LoadedModules -> Bool
isLoaded mn lm = any ((mn ==) . lmName) (getLoadedModules lm)
lookupModule :: ModName -> ModuleEnv -> Maybe LoadedModule
lookupModule mn env = List.find ((mn ==) . lmName) (getLoadedModules (meLoadedModules env))
addLoadedModule :: FilePath -> T.Module -> LoadedModules -> LoadedModules
addLoadedModule path tm lm
| isLoaded (T.mName tm) lm = lm
| otherwise = LoadedModules (getLoadedModules lm ++ [loaded])
where
loaded = LoadedModule
{ lmName = T.mName tm
, lmFilePath = path
, lmInterface = genIface tm
, lmModule = tm
}
removeLoadedModule :: FilePath -> LoadedModules -> LoadedModules
removeLoadedModule path (LoadedModules ms) = LoadedModules (remove ms)
where
remove (lm:rest)
| lmFilePath lm == path = rest
| otherwise = lm : remove rest
remove [] = []
-- Dynamic Environments --------------------------------------------------------
-- | Extra information we need to carry around to dynamically extend
-- an environment outside the context of a single module. Particularly
-- useful when dealing with interactive declarations as in @:let@ or
-- @it@.
data DynamicEnv = DEnv
{ deNames :: R.NamingEnv
, deDecls :: [T.DeclGroup]
, deEnv :: EvalEnv
} deriving (Generic, NFData)
instance Monoid DynamicEnv where
mempty = DEnv
{ deNames = mempty
, deDecls = mempty
, deEnv = mempty
}
mappend de1 de2 = DEnv
{ deNames = deNames de1 <> deNames de2
, deDecls = deDecls de1 <> deDecls de2
, deEnv = deEnv de1 <> deEnv de2
}
-- | Build 'IfaceDecls' that correspond to all of the bindings in the
-- dynamic environment.
--
-- XXX: if we ever add type synonyms or newtypes at the REPL, revisit
-- this.
deIfaceDecls :: DynamicEnv -> IfaceDecls
deIfaceDecls DEnv { deDecls = dgs } =
mconcat [ IfaceDecls
{ ifTySyns = Map.empty
, ifNewtypes = Map.empty
, ifDecls = Map.singleton (ifDeclName ifd) ifd
}
| decl <- concatMap T.groupDecls dgs
, let ifd = mkIfaceDecl decl
]
cryptol-2.4.0/src/Cryptol/ModuleSystem/Interface.hs 0000644 0000000 0000000 00000007524 12737220176 020527 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.ModuleSystem.Interface (
Iface(..)
, IfaceDecls(..)
, IfaceTySyn, ifTySynName
, IfaceNewtype
, IfaceDecl(..), mkIfaceDecl
, genIface
, ifacePrimMap
) where
import Cryptol.ModuleSystem.Name
import Cryptol.TypeCheck.AST
import Cryptol.Utils.Ident (ModName)
import qualified Data.Map as Map
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- | The resulting interface generated by a module that has been typechecked.
data Iface = Iface
{ ifModName :: !ModName
, ifPublic :: IfaceDecls
, ifPrivate :: IfaceDecls
} deriving (Show, Generic, NFData)
data IfaceDecls = IfaceDecls
{ ifTySyns :: Map.Map Name IfaceTySyn
, ifNewtypes :: Map.Map Name IfaceNewtype
, ifDecls :: Map.Map Name IfaceDecl
} deriving (Show, Generic, NFData)
instance Monoid IfaceDecls where
mempty = IfaceDecls Map.empty Map.empty Map.empty
mappend l r = IfaceDecls
{ ifTySyns = Map.union (ifTySyns l) (ifTySyns r)
, ifNewtypes = Map.union (ifNewtypes l) (ifNewtypes r)
, ifDecls = Map.union (ifDecls l) (ifDecls r)
}
mconcat ds = IfaceDecls
{ ifTySyns = Map.unions (map ifTySyns ds)
, ifNewtypes = Map.unions (map ifNewtypes ds)
, ifDecls = Map.unions (map ifDecls ds)
}
type IfaceTySyn = TySyn
ifTySynName :: TySyn -> Name
ifTySynName = tsName
type IfaceNewtype = Newtype
data IfaceDecl = IfaceDecl
{ ifDeclName :: !Name
, ifDeclSig :: Schema
, ifDeclPragmas :: [Pragma]
, ifDeclInfix :: Bool
, ifDeclFixity :: Maybe Fixity
, ifDeclDoc :: Maybe String
} deriving (Show, Generic, NFData)
mkIfaceDecl :: Decl -> IfaceDecl
mkIfaceDecl d = IfaceDecl
{ ifDeclName = dName d
, ifDeclSig = dSignature d
, ifDeclPragmas = dPragmas d
, ifDeclInfix = dInfix d
, ifDeclFixity = dFixity d
, ifDeclDoc = dDoc d
}
-- | Generate an Iface from a typechecked module.
genIface :: Module -> Iface
genIface m = Iface
{ ifModName = mName m
, ifPublic = IfaceDecls
{ ifTySyns = tsPub
, ifNewtypes = ntPub
, ifDecls = dPub
}
, ifPrivate = IfaceDecls
{ ifTySyns = tsPriv
, ifNewtypes = ntPriv
, ifDecls = dPriv
}
}
where
(tsPub,tsPriv) =
Map.partitionWithKey (\ qn _ -> qn `isExportedType` mExports m ) (mTySyns m)
(ntPub,ntPriv) =
Map.partitionWithKey (\ qn _ -> qn `isExportedType` mExports m ) (mNewtypes m)
(dPub,dPriv) =
Map.partitionWithKey (\ qn _ -> qn `isExportedBind` mExports m)
$ Map.fromList [ (qn,mkIfaceDecl d) | dg <- mDecls m
, d <- groupDecls dg
, let qn = dName d
]
-- | Produce a PrimMap from an interface.
--
-- NOTE: the map will expose /both/ public and private names.
ifacePrimMap :: Iface -> PrimMap
ifacePrimMap Iface { .. } =
PrimMap { primDecls = merge primDecls
, primTypes = merge primTypes }
where
merge f = Map.union (f public) (f private)
public = ifaceDeclsPrimMap ifPublic
private = ifaceDeclsPrimMap ifPrivate
ifaceDeclsPrimMap :: IfaceDecls -> PrimMap
ifaceDeclsPrimMap IfaceDecls { .. } =
PrimMap { primDecls = Map.fromList (newtypes ++ exprs)
, primTypes = Map.fromList (newtypes ++ types)
}
where
exprs = [ (nameIdent n, n) | n <- Map.keys ifDecls ]
newtypes = [ (nameIdent n, n) | n <- Map.keys ifNewtypes ]
types = [ (nameIdent n, n) | n <- Map.keys ifTySyns ]
cryptol-2.4.0/src/Cryptol/ModuleSystem/Monad.hs 0000644 0000000 0000000 00000032624 12737220176 017664 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.ModuleSystem.Monad where
import Cryptol.Eval.Env (EvalEnv)
import Cryptol.ModuleSystem.Env
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Name (FreshM(..),Supply)
import Cryptol.ModuleSystem.Renamer
(RenamerError(),RenamerWarning(),NamingEnv)
import qualified Cryptol.Parser as Parser
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.Position (Located)
import Cryptol.Utils.Panic (panic)
import qualified Cryptol.Parser.NoPat as NoPat
import qualified Cryptol.Parser.NoInclude as NoInc
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.TypeCheck.AST as T
import Cryptol.Parser.Position (Range)
import Cryptol.Utils.Ident (interactiveName)
import Cryptol.Utils.PP
import Control.Exception (IOException)
import Data.Function (on)
import Data.Maybe (isJust)
import MonadLib
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- Errors ----------------------------------------------------------------------
data ImportSource
= FromModule P.ModName
| FromImport (Located P.Import)
deriving (Show, Generic, NFData)
instance Eq ImportSource where
(==) = (==) `on` importedModule
instance PP ImportSource where
ppPrec _ is = case is of
FromModule n -> text "module name" <+> pp n
FromImport li -> text "import of module" <+> pp (P.iModule (P.thing li))
importedModule :: ImportSource -> P.ModName
importedModule is = case is of
FromModule n -> n
FromImport li -> P.iModule (P.thing li)
data ModuleError
= ModuleNotFound P.ModName [FilePath]
-- ^ Unable to find the module given, tried looking in these paths
| CantFindFile FilePath
-- ^ Unable to open a file
| OtherIOError FilePath IOException
-- ^ Some other IO error occurred while reading this file
| ModuleParseError FilePath Parser.ParseError
-- ^ Generated this parse error when parsing the file for module m
| RecursiveModules [ImportSource]
-- ^ Recursive module group discovered
| RenamerErrors ImportSource [RenamerError]
-- ^ Problems during the renaming phase
| NoPatErrors ImportSource [NoPat.Error]
-- ^ Problems during the NoPat phase
| NoIncludeErrors ImportSource [NoInc.IncludeError]
-- ^ Problems during the NoInclude phase
| TypeCheckingFailed ImportSource [(Range,T.Error)]
-- ^ Problems during type checking
| OtherFailure String
-- ^ Problems after type checking, eg. specialization
| ModuleNameMismatch P.ModName (Located P.ModName)
-- ^ Module loaded by 'import' statement has the wrong module name
| DuplicateModuleName P.ModName FilePath FilePath
-- ^ Two modules loaded from different files have the same module name
deriving (Show)
instance NFData ModuleError where
rnf e = case e of
ModuleNotFound src path -> src `deepseq` path `deepseq` ()
CantFindFile path -> path `deepseq` ()
OtherIOError path exn -> path `deepseq` exn `seq` ()
ModuleParseError source err -> source `deepseq` err `deepseq` ()
RecursiveModules mods -> mods `deepseq` ()
RenamerErrors src errs -> src `deepseq` errs `deepseq` ()
NoPatErrors src errs -> src `deepseq` errs `deepseq` ()
NoIncludeErrors src errs -> src `deepseq` errs `deepseq` ()
TypeCheckingFailed src errs -> src `deepseq` errs `deepseq` ()
ModuleNameMismatch expected found ->
expected `deepseq` found `deepseq` ()
DuplicateModuleName name path1 path2 ->
name `deepseq` path1 `deepseq` path2 `deepseq` ()
OtherFailure x -> x `deepseq` ()
instance PP ModuleError where
ppPrec _ e = case e of
ModuleNotFound src path ->
text "[error]" <+>
text "Could not find module" <+> pp src
$$
hang (text "Searched paths:")
4 (vcat (map text path))
$$
text "Set the CRYPTOLPATH environment variable to search more directories"
CantFindFile path ->
text "[error]" <+>
text "can't find file:" <+> text path
OtherIOError path exn ->
hang (text "[error]" <+>
text "IO error while loading file:" <+> text path <> colon)
4 (text (show exn))
ModuleParseError _source err -> Parser.ppError err
RecursiveModules mods ->
hang (text "[error] module imports form a cycle:")
4 (vcat (map pp (reverse mods)))
RenamerErrors _src errs -> vcat (map pp errs)
NoPatErrors _src errs -> vcat (map pp errs)
NoIncludeErrors _src errs -> vcat (map NoInc.ppIncludeError errs)
TypeCheckingFailed _src errs -> vcat (map T.ppError errs)
ModuleNameMismatch expected found ->
hang (text "[error]" <+> pp (P.srcRange found) <> char ':')
4 (vcat [ text "File name does not match module name:"
, text "Saw:" <+> pp (P.thing found)
, text "Expected:" <+> pp expected
])
DuplicateModuleName name path1 path2 ->
hang (text "[error] module" <+> pp name <+>
text "is defined in multiple files:")
4 (vcat [text path1, text path2])
OtherFailure x -> text x
moduleNotFound :: P.ModName -> [FilePath] -> ModuleM a
moduleNotFound name paths = ModuleT (raise (ModuleNotFound name paths))
cantFindFile :: FilePath -> ModuleM a
cantFindFile path = ModuleT (raise (CantFindFile path))
otherIOError :: FilePath -> IOException -> ModuleM a
otherIOError path exn = ModuleT (raise (OtherIOError path exn))
moduleParseError :: FilePath -> Parser.ParseError -> ModuleM a
moduleParseError path err =
ModuleT (raise (ModuleParseError path err))
recursiveModules :: [ImportSource] -> ModuleM a
recursiveModules loaded = ModuleT (raise (RecursiveModules loaded))
renamerErrors :: [RenamerError] -> ModuleM a
renamerErrors errs = do
src <- getImportSource
ModuleT (raise (RenamerErrors src errs))
noPatErrors :: [NoPat.Error] -> ModuleM a
noPatErrors errs = do
src <- getImportSource
ModuleT (raise (NoPatErrors src errs))
noIncludeErrors :: [NoInc.IncludeError] -> ModuleM a
noIncludeErrors errs = do
src <- getImportSource
ModuleT (raise (NoIncludeErrors src errs))
typeCheckingFailed :: [(Range,T.Error)] -> ModuleM a
typeCheckingFailed errs = do
src <- getImportSource
ModuleT (raise (TypeCheckingFailed src errs))
moduleNameMismatch :: P.ModName -> Located P.ModName -> ModuleM a
moduleNameMismatch expected found =
ModuleT (raise (ModuleNameMismatch expected found))
duplicateModuleName :: P.ModName -> FilePath -> FilePath -> ModuleM a
duplicateModuleName name path1 path2 =
ModuleT (raise (DuplicateModuleName name path1 path2))
-- Warnings --------------------------------------------------------------------
data ModuleWarning
= TypeCheckWarnings [(Range,T.Warning)]
| RenamerWarnings [RenamerWarning]
deriving (Show, Generic, NFData)
instance PP ModuleWarning where
ppPrec _ w = case w of
TypeCheckWarnings ws -> vcat (map T.ppWarning ws)
RenamerWarnings ws -> vcat (map pp ws)
warn :: [ModuleWarning] -> ModuleM ()
warn = ModuleT . put
typeCheckWarnings :: [(Range,T.Warning)] -> ModuleM ()
typeCheckWarnings ws
| null ws = return ()
| otherwise = warn [TypeCheckWarnings ws]
renamerWarnings :: [RenamerWarning] -> ModuleM ()
renamerWarnings ws
| null ws = return ()
| otherwise = warn [RenamerWarnings ws]
-- Module System Monad ---------------------------------------------------------
data RO = RO
{ roLoading :: [ImportSource]
}
emptyRO :: RO
emptyRO = RO { roLoading = [] }
newtype ModuleT m a = ModuleT
{ unModuleT :: ReaderT RO (StateT ModuleEnv
(ExceptionT ModuleError (WriterT [ModuleWarning] m))) a
}
instance Monad m => Functor (ModuleT m) where
{-# INLINE fmap #-}
fmap f m = ModuleT (fmap f (unModuleT m))
instance Monad m => Applicative (ModuleT m) where
{-# INLINE pure #-}
pure x = ModuleT (pure x)
{-# INLINE (<*>) #-}
l <*> r = ModuleT (unModuleT l <*> unModuleT r)
instance Monad m => Monad (ModuleT m) where
{-# INLINE return #-}
return x = ModuleT (return x)
{-# INLINE (>>=) #-}
m >>= f = ModuleT (unModuleT m >>= unModuleT . f)
{-# INLINE fail #-}
fail = ModuleT . raise . OtherFailure
instance MonadT ModuleT where
{-# INLINE lift #-}
lift = ModuleT . lift . lift . lift . lift
instance Monad m => FreshM (ModuleT m) where
liftSupply f = ModuleT $
do me <- get
let (a,s') = f (meSupply me)
set $! me { meSupply = s' }
return a
runModuleT :: Monad m
=> ModuleEnv
-> ModuleT m a
-> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
runModuleT env m =
runWriterT
$ runExceptionT
$ runStateT env
$ runReaderT emptyRO
$ unModuleT m
-- runM (unModuleT m) emptyRO env
type ModuleM = ModuleT IO
runModuleM :: ModuleEnv -> ModuleM a
-> IO (Either ModuleError (a,ModuleEnv),[ModuleWarning])
runModuleM = runModuleT
io :: BaseM m IO => IO a -> ModuleT m a
io m = ModuleT (inBase m)
getModuleEnv :: Monad m => ModuleT m ModuleEnv
getModuleEnv = ModuleT get
setModuleEnv :: Monad m => ModuleEnv -> ModuleT m ()
setModuleEnv = ModuleT . set
modifyModuleEnv :: Monad m => (ModuleEnv -> ModuleEnv) -> ModuleT m ()
modifyModuleEnv f = ModuleT $ do
env <- get
set $! f env
isLoaded :: P.ModName -> ModuleM Bool
isLoaded mn = ModuleT $ do
env <- get
return (isJust (lookupModule mn env))
loadingImport :: Located P.Import -> ModuleM a -> ModuleM a
loadingImport = loading . FromImport
loadingModule :: P.ModName -> ModuleM a -> ModuleM a
loadingModule = loading . FromModule
-- | Push an "interactive" context onto the loading stack. A bit of a hack, as
-- it uses a faked module name
interactive :: ModuleM a -> ModuleM a
interactive = loadingModule interactiveName
loading :: ImportSource -> ModuleM a -> ModuleM a
loading src m = ModuleT $ do
ro <- ask
let ro' = ro { roLoading = src : roLoading ro }
-- check for recursive modules
when (src `elem` roLoading ro) (raise (RecursiveModules (roLoading ro')))
local ro' (unModuleT m)
-- | Get the currently focused import source.
getImportSource :: ModuleM ImportSource
getImportSource = ModuleT $ do
ro <- ask
case roLoading ro of
is : _ -> return is
_ -> panic "ModuleSystem: getImportSource" ["Import stack is empty"]
getIface :: P.ModName -> ModuleM Iface
getIface mn = ModuleT $ do
env <- get
case lookupModule mn env of
Just lm -> return (lmInterface lm)
Nothing -> panic "ModuleSystem" ["Interface not available "]
getNameSeeds :: ModuleM T.NameSeeds
getNameSeeds = ModuleT (meNameSeeds `fmap` get)
getSupply :: ModuleM Supply
getSupply = ModuleT (meSupply `fmap` get)
getMonoBinds :: ModuleM Bool
getMonoBinds = ModuleT (meMonoBinds `fmap` get)
setMonoBinds :: Bool -> ModuleM ()
setMonoBinds b = ModuleT $ do
env <- get
set $! env { meMonoBinds = b }
setNameSeeds :: T.NameSeeds -> ModuleM ()
setNameSeeds seeds = ModuleT $ do
env <- get
set $! env { meNameSeeds = seeds }
setSupply :: Supply -> ModuleM ()
setSupply supply = ModuleT $
do env <- get
set $! env { meSupply = supply }
-- | Remove a module from the set of loaded module, by its path.
unloadModule :: FilePath -> ModuleM ()
unloadModule path = ModuleT $ do
env <- get
set $! env { meLoadedModules = removeLoadedModule path (meLoadedModules env) }
loadedModule :: FilePath -> T.Module -> ModuleM ()
loadedModule path m = ModuleT $ do
env <- get
set $! env { meLoadedModules = addLoadedModule path m (meLoadedModules env) }
modifyEvalEnv :: (EvalEnv -> EvalEnv) -> ModuleM ()
modifyEvalEnv f = ModuleT $ do
env <- get
set $! env { meEvalEnv = f (meEvalEnv env) }
getEvalEnv :: ModuleM EvalEnv
getEvalEnv = ModuleT (meEvalEnv `fmap` get)
getFocusedModule :: ModuleM (Maybe P.ModName)
getFocusedModule = ModuleT (meFocusedModule `fmap` get)
setFocusedModule :: P.ModName -> ModuleM ()
setFocusedModule n = ModuleT $ do
me <- get
set $! me { meFocusedModule = Just n }
getSearchPath :: ModuleM [FilePath]
getSearchPath = ModuleT (meSearchPath `fmap` get)
-- | Run a 'ModuleM' action in a context with a prepended search
-- path. Useful for temporarily looking in other places while
-- resolving imports, for example.
withPrependedSearchPath :: [FilePath] -> ModuleM a -> ModuleM a
withPrependedSearchPath fps m = ModuleT $ do
env0 <- get
let fps0 = meSearchPath env0
set $! env0 { meSearchPath = fps ++ fps0 }
x <- unModuleT m
env <- get
set $! env { meSearchPath = fps0 }
return x
-- XXX improve error handling here
getFocusedEnv :: ModuleM (IfaceDecls,NamingEnv,NameDisp)
getFocusedEnv = ModuleT (focusedEnv `fmap` get)
getQualifiedEnv :: ModuleM IfaceDecls
getQualifiedEnv = ModuleT (qualifiedEnv `fmap` get)
getDynEnv :: ModuleM DynamicEnv
getDynEnv = ModuleT (meDynEnv `fmap` get)
setDynEnv :: DynamicEnv -> ModuleM ()
setDynEnv denv = ModuleT $ do
me <- get
set $! me { meDynEnv = denv }
setSolver :: T.SolverConfig -> ModuleM ()
setSolver cfg = ModuleT $ do
me <- get
set $! me { meSolverConfig = cfg }
getSolverConfig :: ModuleM T.SolverConfig
getSolverConfig = ModuleT $ do
me <- get
return (meSolverConfig me)
cryptol-2.4.0/src/Cryptol/ModuleSystem/Name.hs 0000644 0000000 0000000 00000022717 12737220176 017510 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
-- for the instances of RunM and BaseM
{-# LANGUAGE UndecidableInstances #-}
module Cryptol.ModuleSystem.Name (
-- * Names
Name(), NameInfo(..)
, nameUnique
, nameIdent
, nameInfo
, nameLoc
, nameFixity
, asPrim
, cmpNameLexical
, cmpNameDisplay
, ppLocName
-- ** Creation
, mkDeclared
, mkParameter
-- ** Unique Supply
, FreshM(..), nextUniqueM
, SupplyT(), runSupplyT
, Supply(), emptySupply, nextUnique
-- ** PrimMap
, PrimMap(..)
, lookupPrimDecl
, lookupPrimType
) where
import Cryptol.Parser.AST( Fixity(..) )
import Cryptol.Parser.Position (Range,Located(..))
import Cryptol.Utils.Ident
import Cryptol.Utils.Panic
import Cryptol.Utils.PP
import Control.DeepSeq
import Control.Monad.Fix (MonadFix(mfix))
import qualified Data.Map as Map
import qualified Data.Monoid as M
import Data.Ord (comparing)
import GHC.Generics (Generic)
import MonadLib
import Prelude ()
import Prelude.Compat
-- Names -----------------------------------------------------------------------
-- | Information about the binding site of the name.
data NameInfo = Declared !ModName
-- ^ This name refers to a declaration from this module
| Parameter
-- ^ This name is a parameter (function or type)
deriving (Eq, Show, Generic, NFData)
data Name = Name { nUnique :: {-# UNPACK #-} !Int
-- ^ INVARIANT: this field uniquely identifies a name for one
-- session with the Cryptol library. Names are unique to
-- their binding site.
, nInfo :: !NameInfo
-- ^ Information about the origin of this name.
, nIdent :: !Ident
-- ^ The name of the identifier
, nFixity :: !(Maybe Fixity)
-- ^ The associativity and precedence level of
-- infix operators. 'Nothing' indicates an
-- ordinary prefix operator.
, nLoc :: !Range
-- ^ Where this name was defined
} deriving (Show, Generic, NFData)
instance Eq Name where
a == b = compare a b == EQ
a /= b = compare a b /= EQ
instance Ord Name where
compare a b = compare (nUnique a) (nUnique b)
-- | Compare two names lexically.
cmpNameLexical :: Name -> Name -> Ordering
cmpNameLexical l r =
case (nameInfo l, nameInfo r) of
(Declared nsl,Declared nsr) ->
case compare nsl nsr of
EQ -> comparing nameIdent l r
cmp -> cmp
(Parameter,Parameter) -> comparing nameIdent l r
(Declared nsl,Parameter) -> compare nsl (identText (nameIdent r))
(Parameter,Declared nsr) -> compare (identText (nameIdent l)) nsr
-- | Compare two names by the way they would be displayed.
cmpNameDisplay :: NameDisp -> Name -> Name -> Ordering
cmpNameDisplay disp l r =
case (nameInfo l, nameInfo r) of
(Declared nsl, Declared nsr) ->
let pfxl = fmtModName nsl (getNameFormat nsl (nameIdent l) disp)
pfxr = fmtModName nsr (getNameFormat nsr (nameIdent r) disp)
in case compare pfxl pfxr of
EQ -> compare (nameIdent l) (nameIdent r)
cmp -> cmp
(Parameter,Parameter) ->
compare (nameIdent l) (nameIdent r)
(Declared nsl,Parameter) ->
let pfxl = fmtModName nsl (getNameFormat nsl (nameIdent l) disp)
in case compare pfxl (identText (nameIdent r)) of
EQ -> GT
cmp -> cmp
(Parameter,Declared nsr) ->
let pfxr = fmtModName nsr (getNameFormat nsr (nameIdent r) disp)
in case compare (identText (nameIdent l)) pfxr of
EQ -> LT
cmp -> cmp
-- | Figure out how the name should be displayed, by referencing the display
-- function in the environment. NOTE: this function doesn't take into account
-- the need for parenthesis.
ppName :: Name -> Doc
ppName Name { .. } =
case nInfo of
Declared m -> withNameDisp $ \disp ->
case getNameFormat m nIdent disp of
Qualified m' -> pp m' <> text "::" <> pp nIdent
UnQualified -> pp nIdent
NotInScope -> pp m <> text "::" <> pp nIdent
Parameter -> pp nIdent
instance PP Name where
ppPrec _ = ppPrefixName
instance PPName Name where
ppNameFixity n = fmap (\(Fixity a i) -> (a,i)) $ nameFixity n
ppInfixName n @ Name { .. }
| isInfixIdent nIdent = ppName n
| otherwise = panic "Name" [ "Non-infix name used infix"
, show nIdent ]
ppPrefixName n @ Name { .. } = optParens (isInfixIdent nIdent) (ppName n)
-- | Pretty-print a name with its source location information.
ppLocName :: Name -> Doc
ppLocName n = pp Located { srcRange = nameLoc n, thing = n }
nameUnique :: Name -> Int
nameUnique = nUnique
nameIdent :: Name -> Ident
nameIdent = nIdent
nameInfo :: Name -> NameInfo
nameInfo = nInfo
nameLoc :: Name -> Range
nameLoc = nLoc
nameFixity :: Name -> Maybe Fixity
nameFixity = nFixity
asPrim :: Name -> Maybe Ident
asPrim Name { .. }
| nInfo == Declared preludeName = Just nIdent
| otherwise = Nothing
-- Name Supply -----------------------------------------------------------------
class Monad m => FreshM m where
liftSupply :: (Supply -> (a,Supply)) -> m a
instance FreshM m => FreshM (ExceptionT i m) where
liftSupply f = lift (liftSupply f)
instance (M.Monoid i, FreshM m) => FreshM (WriterT i m) where
liftSupply f = lift (liftSupply f)
instance FreshM m => FreshM (ReaderT i m) where
liftSupply f = lift (liftSupply f)
instance FreshM m => FreshM (StateT i m) where
liftSupply f = lift (liftSupply f)
instance Monad m => FreshM (SupplyT m) where
liftSupply f = SupplyT $
do s <- get
let (a,s') = f s
set $! s'
return a
-- | A monad for easing the use of the supply.
newtype SupplyT m a = SupplyT { unSupply :: StateT Supply m a }
runSupplyT :: Monad m => Supply -> SupplyT m a -> m (a,Supply)
runSupplyT s (SupplyT m) = runStateT s m
instance Monad m => Functor (SupplyT m) where
fmap f (SupplyT m) = SupplyT (fmap f m)
{-# INLINE fmap #-}
instance Monad m => Applicative (SupplyT m) where
pure x = SupplyT (pure x)
{-# INLINE pure #-}
f <*> g = SupplyT (unSupply f <*> unSupply g)
{-# INLINE (<*>) #-}
instance Monad m => Monad (SupplyT m) where
return = pure
{-# INLINE return #-}
m >>= f = SupplyT (unSupply m >>= unSupply . f)
{-# INLINE (>>=) #-}
instance MonadT SupplyT where
lift m = SupplyT (lift m)
instance BaseM m n => BaseM (SupplyT m) n where
inBase m = SupplyT (inBase m)
{-# INLINE inBase #-}
instance RunM m (a,Supply) r => RunM (SupplyT m) a (Supply -> r) where
runM (SupplyT m) s = runM m s
{-# INLINE runM #-}
instance MonadFix m => MonadFix (SupplyT m) where
mfix f = SupplyT (mfix (unSupply . f))
-- | Retrieve the next unique from the supply.
nextUniqueM :: FreshM m => m Int
nextUniqueM = liftSupply nextUnique
data Supply = Supply !Int
deriving (Show, Generic, NFData)
-- | This should only be used once at library initialization, and threaded
-- through the rest of the session. The supply is started at 0x1000 to leave us
-- plenty of room for names that the compiler needs to know about (wired-in
-- constants).
emptySupply :: Supply
emptySupply = Supply 0
nextUnique :: Supply -> (Int,Supply)
nextUnique (Supply n) = s' `seq` (n,s')
where
s' = Supply (n + 1)
-- Name Construction -----------------------------------------------------------
-- | Make a new name for a declaration.
mkDeclared :: ModName -> Ident -> Maybe Fixity -> Range -> Supply -> (Name,Supply)
mkDeclared m nIdent nFixity nLoc s =
let (nUnique,s') = nextUnique s
nInfo = Declared m
in (Name { .. }, s')
-- | Make a new parameter name.
mkParameter :: Ident -> Range -> Supply -> (Name,Supply)
mkParameter nIdent nLoc s =
let (nUnique,s') = nextUnique s
nFixity = Nothing
in (Name { nInfo = Parameter, .. }, s')
-- Prim Maps -------------------------------------------------------------------
-- | A mapping from an identifier defined in some module to its real name.
data PrimMap = PrimMap { primDecls :: Map.Map Ident Name
, primTypes :: Map.Map Ident Name
} deriving (Show, Generic, NFData)
lookupPrimDecl, lookupPrimType :: Ident -> PrimMap -> Name
-- | It's assumed that we're looking things up that we know already exist, so
-- this will panic if it doesn't find the name.
lookupPrimDecl name PrimMap { .. } = Map.findWithDefault err name primDecls
where
err = panic "Cryptol.ModuleSystem.Name.lookupPrimDecl"
[ "Unknown declaration: " ++ show name
, show primDecls ]
-- | It's assumed that we're looking things up that we know already exist, so
-- this will panic if it doesn't find the name.
lookupPrimType name PrimMap { .. } = Map.findWithDefault err name primTypes
where
err = panic "Cryptol.ModuleSystem.Name.lookupPrimType"
[ "Unknown type: " ++ show name
, show primTypes ]
cryptol-2.4.0/src/Cryptol/ModuleSystem/NamingEnv.hs 0000644 0000000 0000000 00000027234 12737220176 020511 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.ModuleSystem.NamingEnv where
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Name
import Cryptol.Parser.AST
import Cryptol.Parser.Position
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import Data.List (nub)
import Data.Maybe (catMaybes,fromMaybe)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import MonadLib (runId,Id)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- Naming Environment ----------------------------------------------------------
-- XXX The fixity environment should be removed, and Name should include fixity
-- information.
data NamingEnv = NamingEnv { neExprs :: !(Map.Map PName [Name])
-- ^ Expr renaming environment
, neTypes :: !(Map.Map PName [Name])
-- ^ Type renaming environment
, neFixity:: !(Map.Map Name Fixity)
-- ^ Expression-level fixity environment
} deriving (Show, Generic, NFData)
instance Monoid NamingEnv where
mempty =
NamingEnv { neExprs = Map.empty
, neTypes = Map.empty
, neFixity = Map.empty }
-- NOTE: merging the fixity maps is a special case that just prefers the left
-- entry, as they're already keyed by a name with a unique
mappend l r =
NamingEnv { neExprs = Map.unionWith merge (neExprs l) (neExprs r)
, neTypes = Map.unionWith merge (neTypes l) (neTypes r)
, neFixity = Map.union (neFixity l) (neFixity r) }
mconcat envs =
NamingEnv { neExprs = Map.unionsWith merge (map neExprs envs)
, neTypes = Map.unionsWith merge (map neTypes envs)
, neFixity = Map.unions (map neFixity envs) }
{-# INLINE mempty #-}
{-# INLINE mappend #-}
{-# INLINE mconcat #-}
-- | Merge two name maps, collapsing cases where the entries are the same, and
-- producing conflicts otherwise.
merge :: [Name] -> [Name] -> [Name]
merge xs ys | xs == ys = xs
| otherwise = nub (xs ++ ys)
-- | Generate a mapping from 'Ident' to 'Name' for a given naming environment.
toPrimMap :: NamingEnv -> PrimMap
toPrimMap NamingEnv { .. } = PrimMap { .. }
where
primDecls = Map.fromList [ (nameIdent n,n) | ns <- Map.elems neExprs
, n <- ns ]
primTypes = Map.fromList [ (nameIdent n,n) | ns <- Map.elems neTypes
, n <- ns ]
-- | Generate a display format based on a naming environment.
toNameDisp :: NamingEnv -> NameDisp
toNameDisp NamingEnv { .. } = NameDisp display
where
display mn ident = Map.lookup (mn,ident) names
-- only format declared names, as parameters don't need any special
-- formatting.
names = Map.fromList
$ [ mkEntry pn mn (nameIdent n) | (pn,ns) <- Map.toList neExprs
, n <- ns
, Declared mn <- [nameInfo n] ]
++ [ mkEntry pn mn (nameIdent n) | (pn,ns) <- Map.toList neTypes
, n <- ns
, Declared mn <- [nameInfo n] ]
mkEntry pn mn i = ((mn,i),fmt)
where
fmt = case getModName pn of
Just ns -> Qualified ns
Nothing -> UnQualified
-- | Produce sets of visible names for types and declarations.
--
-- NOTE: if entries in the NamingEnv would have produced a name clash, they will
-- be omitted from the resulting sets.
visibleNames :: NamingEnv -> ({- types -} Set.Set Name
,{- decls -} Set.Set Name)
visibleNames NamingEnv { .. } = (types,decls)
where
types = Set.fromList [ n | [n] <- Map.elems neTypes ]
decls = Set.fromList [ n | [n] <- Map.elems neExprs ]
-- | Qualify all symbols in a 'NamingEnv' with the given prefix.
qualify :: ModName -> NamingEnv -> NamingEnv
qualify pfx NamingEnv { .. } =
NamingEnv { neExprs = Map.mapKeys toQual neExprs
, neTypes = Map.mapKeys toQual neTypes
, .. }
where
-- XXX we don't currently qualify fresh names
toQual (Qual _ n) = Qual pfx n
toQual (UnQual n) = Qual pfx n
toQual n@NewName{} = n
filterNames :: (PName -> Bool) -> NamingEnv -> NamingEnv
filterNames p NamingEnv { .. } =
NamingEnv { neExprs = Map.filterWithKey check neExprs
, neTypes = Map.filterWithKey check neTypes
, .. }
where
check :: PName -> a -> Bool
check n _ = p n
-- | Singleton type renaming environment.
singletonT :: PName -> Name -> NamingEnv
singletonT qn tn = mempty { neTypes = Map.singleton qn [tn] }
-- | Singleton expression renaming environment.
singletonE :: PName -> Name -> NamingEnv
singletonE qn en = mempty { neExprs = Map.singleton qn [en] }
-- | Like mappend, but when merging, prefer values on the lhs.
shadowing :: NamingEnv -> NamingEnv -> NamingEnv
shadowing l r = NamingEnv
{ neExprs = Map.union (neExprs l) (neExprs r)
, neTypes = Map.union (neTypes l) (neTypes r)
, neFixity = Map.union (neFixity l) (neFixity r) }
travNamingEnv :: Applicative f => (Name -> f Name) -> NamingEnv -> f NamingEnv
travNamingEnv f ne = NamingEnv <$> neExprs' <*> neTypes' <*> pure (neFixity ne)
where
neExprs' = traverse (traverse f) (neExprs ne)
neTypes' = traverse (traverse f) (neTypes ne)
data InModule a = InModule !ModName a
deriving (Functor,Traversable,Foldable,Show)
-- | Generate a 'NamingEnv' using an explicit supply.
namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv,Supply)
namingEnv' a supply = runId (runSupplyT supply (runBuild (namingEnv a)))
newtype BuildNamingEnv = BuildNamingEnv { runBuild :: SupplyT Id NamingEnv }
instance Monoid BuildNamingEnv where
mempty = BuildNamingEnv (pure mempty)
mappend (BuildNamingEnv a) (BuildNamingEnv b) = BuildNamingEnv $
do x <- a
y <- b
return (mappend x y)
mconcat bs = BuildNamingEnv $
do ns <- sequence (map runBuild bs)
return (mconcat ns)
-- | Things that define exported names.
class BindsNames a where
namingEnv :: a -> BuildNamingEnv
instance BindsNames NamingEnv where
namingEnv env = BuildNamingEnv (return env)
{-# INLINE namingEnv #-}
instance BindsNames a => BindsNames (Maybe a) where
namingEnv = foldMap namingEnv
{-# INLINE namingEnv #-}
instance BindsNames a => BindsNames [a] where
namingEnv = foldMap namingEnv
{-# INLINE namingEnv #-}
-- | Generate a type renaming environment from the parameters that are bound by
-- this schema.
instance BindsNames (Schema PName) where
namingEnv (Forall ps _ _ _) = foldMap namingEnv ps
{-# INLINE namingEnv #-}
-- | Interpret an import in the context of an interface, to produce a name
-- environment for the renamer, and a 'NameDisp' for pretty-printing.
interpImport :: Import -> IfaceDecls -> NamingEnv
interpImport imp publicDecls = qualified
where
-- optionally qualify names based on the import
qualified | Just pfx <- iAs imp = qualify pfx restricted
| otherwise = restricted
-- restrict or hide imported symbols
restricted
| Just (Hiding ns) <- iSpec imp =
filterNames (\qn -> not (getIdent qn `elem` ns)) public
| Just (Only ns) <- iSpec imp =
filterNames (\qn -> getIdent qn `elem` ns) public
| otherwise = public
-- generate the initial environment from the public interface, where no names
-- are qualified
public = unqualifiedEnv publicDecls
-- | Generate a naming environment from a declaration interface, where none of
-- the names are qualified.
unqualifiedEnv :: IfaceDecls -> NamingEnv
unqualifiedEnv IfaceDecls { .. } =
mconcat [ exprs, tySyns, ntTypes, ntExprs
, mempty { neFixity = Map.fromList fixity } ]
where
toPName n = mkUnqual (nameIdent n)
exprs = mconcat [ singletonE (toPName n) n | n <- Map.keys ifDecls ]
tySyns = mconcat [ singletonT (toPName n) n | n <- Map.keys ifTySyns ]
ntTypes = mconcat [ singletonT (toPName n) n | n <- Map.keys ifNewtypes ]
ntExprs = mconcat [ singletonE (toPName n) n | n <- Map.keys ifNewtypes ]
fixity =
catMaybes [ do f <- ifDeclFixity d; return (ifDeclName d,f)
| d <- Map.elems ifDecls ]
data ImportIface = ImportIface Import Iface
-- | Produce a naming environment from an interface file, that contains a
-- mapping only from unqualified names to qualified ones.
instance BindsNames ImportIface where
namingEnv (ImportIface imp Iface { .. }) = BuildNamingEnv $
return (interpImport imp ifPublic)
{-# INLINE namingEnv #-}
-- | Introduce the name
instance BindsNames (InModule (Bind PName)) where
namingEnv (InModule ns b) = BuildNamingEnv $
do let Located { .. } = bName b
n <- liftSupply (mkDeclared ns (getIdent thing) (bFixity b) srcRange)
let fixity = case bFixity b of
Just f -> mempty { neFixity = Map.singleton n f }
Nothing -> mempty
return (singletonE thing n `mappend` fixity)
-- | Generate the naming environment for a type parameter.
instance BindsNames (TParam PName) where
namingEnv TParam { .. } = BuildNamingEnv $
do let range = fromMaybe emptyRange tpRange
n <- liftSupply (mkParameter (getIdent tpName) range)
return (singletonT tpName n)
-- | The naming environment for a single module. This is the mapping from
-- unqualified names to fully qualified names with uniques.
instance BindsNames (Module PName) where
namingEnv Module { .. } = foldMap (namingEnv . InModule ns) mDecls
where
ns = thing mName
instance BindsNames (InModule (TopDecl PName)) where
namingEnv (InModule ns td) =
case td of
Decl d -> namingEnv (InModule ns (tlValue d))
TDNewtype d -> namingEnv (InModule ns (tlValue d))
Include _ -> mempty
instance BindsNames (InModule (Newtype PName)) where
namingEnv (InModule ns Newtype { .. }) = BuildNamingEnv $
do let Located { .. } = nName
tyName <- liftSupply (mkDeclared ns (getIdent thing) Nothing srcRange)
eName <- liftSupply (mkDeclared ns (getIdent thing) Nothing srcRange)
return (singletonT thing tyName `mappend` singletonE thing eName)
-- | The naming environment for a single declaration.
instance BindsNames (InModule (Decl PName)) where
namingEnv (InModule pfx d) = case d of
DBind b -> BuildNamingEnv $
do n <- mkName (bName b) (bFixity b)
return (singletonE (thing (bName b)) n `mappend` fixity n b)
DSignature ns _sig -> foldMap qualBind ns
DPragma ns _p -> foldMap qualBind ns
DType (TySyn lqn _ _) -> qualType lqn
DLocated d' _ -> namingEnv (InModule pfx d')
DPatBind _pat _e -> panic "ModuleSystem" ["Unexpected pattern binding"]
DFixity{} -> panic "ModuleSystem" ["Unexpected fixity declaration"]
where
mkName ln fx =
liftSupply (mkDeclared pfx (getIdent (thing ln)) fx (srcRange ln))
qualBind ln = BuildNamingEnv $
do n <- mkName ln Nothing
return (singletonE (thing ln) n)
qualType ln = BuildNamingEnv $
do n <- mkName ln Nothing
return (singletonT (thing ln) n)
fixity n b =
case bFixity b of
Just f -> mempty { neFixity = Map.singleton n f }
Nothing -> mempty
cryptol-2.4.0/src/Cryptol/ModuleSystem/Renamer.hs 0000644 0000000 0000000 00000073550 12737220176 020222 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.ModuleSystem.Renamer (
NamingEnv(), shadowing
, BindsNames(..), InModule(..), namingEnv'
, checkNamingEnv
, shadowNames
, Rename(..), runRenamer, RenameM()
, RenamerError(..)
, RenamerWarning(..)
, renameVar
, renameType
, renameModule
) where
import Cryptol.ModuleSystem.Name
import Cryptol.ModuleSystem.NamingEnv
import Cryptol.Prims.Syntax
import Cryptol.Parser.AST
import Cryptol.Parser.Position
import Cryptol.Utils.Ident (packIdent,packInfix)
import Cryptol.Utils.Panic (panic)
import Cryptol.Utils.PP
import qualified Data.Foldable as F
import qualified Data.Map.Strict as Map
import qualified Data.Sequence as Seq
import MonadLib hiding (mapM, mapM_)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- Errors ----------------------------------------------------------------------
data RenamerError
= MultipleSyms (Located PName) [Name] NameDisp
-- ^ Multiple imported symbols contain this name
| UnboundExpr (Located PName) NameDisp
-- ^ Expression name is not bound to any definition
| UnboundType (Located PName) NameDisp
-- ^ Type name is not bound to any definition
| OverlappingSyms [Name] NameDisp
-- ^ An environment has produced multiple overlapping symbols
| ExpectedValue (Located PName) NameDisp
-- ^ When a value is expected from the naming environment, but one or more
-- types exist instead.
| ExpectedType (Located PName) NameDisp
-- ^ When a type is missing from the naming environment, but one or more
-- values exist with the same name.
| FixityError (Located Name) (Located Name) NameDisp
-- ^ When the fixity of two operators conflict
| InvalidConstraint (Type PName) NameDisp
-- ^ When it's not possible to produce a Prop from a Type.
| MalformedBuiltin (Type PName) PName NameDisp
-- ^ When a builtin type/type-function is used incorrectly.
| BoundReservedType PName (Maybe Range) Doc NameDisp
-- ^ When a builtin type is named in a binder.
deriving (Show, Generic, NFData)
instance PP RenamerError where
ppPrec _ e = case e of
MultipleSyms lqn qns disp -> fixNameDisp disp $
hang (text "[error] at" <+> pp (srcRange lqn))
4 $ (text "Multiple definitions for symbol:" <+> pp (thing lqn))
$$ vcat (map ppLocName qns)
UnboundExpr lqn disp -> fixNameDisp disp $
hang (text "[error] at" <+> pp (srcRange lqn))
4 (text "Value not in scope:" <+> pp (thing lqn))
UnboundType lqn disp -> fixNameDisp disp $
hang (text "[error] at" <+> pp (srcRange lqn))
4 (text "Type not in scope:" <+> pp (thing lqn))
OverlappingSyms qns disp -> fixNameDisp disp $
hang (text "[error]")
4 $ text "Overlapping symbols defined:"
$$ vcat (map ppLocName qns)
ExpectedValue lqn disp -> fixNameDisp disp $
hang (text "[error] at" <+> pp (srcRange lqn))
4 (fsep [ text "Expected a value named", quotes (pp (thing lqn))
, text "but found a type instead"
, text "Did you mean `(" <> pp (thing lqn) <> text")?" ])
ExpectedType lqn disp -> fixNameDisp disp $
hang (text "[error] at" <+> pp (srcRange lqn))
4 (fsep [ text "Expected a type named", quotes (pp (thing lqn))
, text "but found a value instead" ])
FixityError o1 o2 disp -> fixNameDisp disp $
hang (text "[error]")
4 (fsep [ text "The fixities of", pp o1, text "and", pp o2
, text "are not compatible. "
, text "You may use explicit parenthesis to disambiguate" ])
InvalidConstraint ty disp -> fixNameDisp disp $
hang (text "[error]" <+> maybe empty (\r -> text "at" <+> pp r) (getLoc ty))
4 (fsep [ pp ty, text "is not a valid constraint" ])
MalformedBuiltin ty pn disp -> fixNameDisp disp $
hang (text "[error]" <+> maybe empty (\r -> text "at" <+> pp r) (getLoc ty))
4 (fsep [ text "invalid use of built-in type", pp pn
, text "in type", pp ty ])
BoundReservedType n loc src disp -> fixNameDisp disp $
hang (text "[error]" <+> maybe empty (\r -> text "at" <+> pp r) loc)
4 (fsep [ text "built-in type", quotes (pp n), text "shadowed in", src ])
-- Warnings --------------------------------------------------------------------
data RenamerWarning
= SymbolShadowed Name [Name] NameDisp
deriving (Show, Generic, NFData)
instance PP RenamerWarning where
ppPrec _ (SymbolShadowed new originals disp) = fixNameDisp disp $
hang (text "[warning] at" <+> loc)
4 $ fsep [ text "This binding for" <+> sym
, (text "shadows the existing binding" <> plural) <+> text "from" ]
$$ vcat (map ppLocName originals)
where
plural | length originals > 1 = char 's'
| otherwise = empty
loc = pp (nameLoc new)
sym = pp new
-- Renaming Monad --------------------------------------------------------------
data RO = RO
{ roLoc :: Range
, roMod :: !ModName
, roNames :: NamingEnv
, roDisp :: !NameDisp
}
data RW = RW
{ rwWarnings :: !(Seq.Seq RenamerWarning)
, rwErrors :: !(Seq.Seq RenamerError)
, rwSupply :: !Supply
}
newtype RenameM a = RenameM
{ unRenameM :: ReaderT RO (StateT RW Lift) a }
instance Monoid a => Monoid (RenameM a) where
{-# INLINE mempty #-}
mempty = return mempty
{-# INLINE mappend #-}
mappend a b =
do x <- a
y <- b
return (mappend x y)
instance Functor RenameM where
{-# INLINE fmap #-}
fmap f m = RenameM (fmap f (unRenameM m))
instance Applicative RenameM where
{-# INLINE pure #-}
pure x = RenameM (pure x)
{-# INLINE (<*>) #-}
l <*> r = RenameM (unRenameM l <*> unRenameM r)
instance Monad RenameM where
{-# INLINE return #-}
return x = RenameM (return x)
{-# INLINE (>>=) #-}
m >>= k = RenameM (unRenameM m >>= unRenameM . k)
instance FreshM RenameM where
liftSupply f = RenameM $ sets $ \ RW { .. } ->
let (a,s') = f rwSupply
rw' = RW { rwSupply = s', .. }
in a `seq` rw' `seq` (a, rw')
runRenamer :: Supply -> ModName -> NamingEnv -> RenameM a
-> (Either [RenamerError] (a,Supply),[RenamerWarning])
runRenamer s ns env m = (res,F.toList (rwWarnings rw))
where
(a,rw) = runM (unRenameM m) RO { roLoc = emptyRange
, roNames = env
, roMod = ns
, roDisp = neverQualifyMod ns
`mappend` toNameDisp env
}
RW { rwErrors = Seq.empty
, rwWarnings = Seq.empty
, rwSupply = s
}
res | Seq.null (rwErrors rw) = Right (a,rwSupply rw)
| otherwise = Left (F.toList (rwErrors rw))
record :: (NameDisp -> RenamerError) -> RenameM ()
record f = RenameM $
do RO { .. } <- ask
RW { .. } <- get
set RW { rwErrors = rwErrors Seq.|> f roDisp, .. }
curLoc :: RenameM Range
curLoc = RenameM (roLoc `fmap` ask)
located :: a -> RenameM (Located a)
located thing =
do srcRange <- curLoc
return Located { .. }
withLoc :: HasLoc loc => loc -> RenameM a -> RenameM a
withLoc loc m = RenameM $ case getLoc loc of
Just range -> do
ro <- ask
local ro { roLoc = range } (unRenameM m)
Nothing -> unRenameM m
-- | Retrieve the name of the current module.
getNS :: RenameM ModName
getNS = RenameM (roMod `fmap` ask)
-- | Shadow the current naming environment with some more names.
shadowNames :: BindsNames env => env -> RenameM a -> RenameM a
shadowNames = shadowNames' CheckAll
data EnvCheck = CheckAll -- ^ Check for overlap and shadowing
| CheckOverlap -- ^ Only check for overlap
| CheckNone -- ^ Don't check the environment
deriving (Eq,Show)
-- | Shadow the current naming environment with some more names. The boolean
-- parameter indicates whether or not to check for shadowing.
shadowNames' :: BindsNames env => EnvCheck -> env -> RenameM a -> RenameM a
shadowNames' check names m = do
do env <- liftSupply (namingEnv' names)
RenameM $
do ro <- ask
env' <- sets (checkEnv (roDisp ro) check env (roNames ro))
let ro' = ro { roNames = env' `shadowing` roNames ro }
local ro' (unRenameM m)
shadowNamesNS :: BindsNames (InModule env) => env -> RenameM a -> RenameM a
shadowNamesNS names m =
do ns <- getNS
shadowNames (InModule ns names) m
-- | Generate warnings when the left environment shadows things defined in
-- the right. Additionally, generate errors when two names overlap in the
-- left environment.
checkEnv :: NameDisp -> EnvCheck -> NamingEnv -> NamingEnv -> RW -> (NamingEnv,RW)
checkEnv disp check l r rw
| check == CheckNone = (l',rw)
| otherwise = (l',rw'')
where
l' = l { neExprs = es, neTypes = ts }
(rw',es) = Map.mapAccumWithKey (step neExprs) rw (neExprs l)
(rw'',ts) = Map.mapAccumWithKey (step neTypes) rw' (neTypes l)
step prj acc k ns = (acc', [head ns])
where
acc' = acc
{ rwWarnings =
if check == CheckAll
then case Map.lookup k (prj r) of
Nothing -> rwWarnings acc
Just os -> rwWarnings acc Seq.|> SymbolShadowed (head ns) os disp
else rwWarnings acc
, rwErrors = rwErrors acc Seq.>< containsOverlap disp ns
}
-- | Check the RHS of a single name rewrite for conflicting sources.
containsOverlap :: NameDisp -> [Name] -> Seq.Seq RenamerError
containsOverlap _ [_] = Seq.empty
containsOverlap _ [] = panic "Renamer" ["Invalid naming environment"]
containsOverlap disp ns = Seq.singleton (OverlappingSyms ns disp)
-- | Throw errors for any names that overlap in a rewrite environment.
checkNamingEnv :: NamingEnv -> ([RenamerError],[RenamerWarning])
checkNamingEnv env = (F.toList out, [])
where
out = Map.foldr check outTys (neExprs env)
outTys = Map.foldr check mempty (neTypes env)
disp = toNameDisp env
check ns acc = containsOverlap disp ns Seq.>< acc
-- Renaming --------------------------------------------------------------------
class Rename f where
rename :: f PName -> RenameM (f Name)
renameModule :: Module PName -> RenameM (NamingEnv,Module Name)
renameModule m =
do env <- liftSupply (namingEnv' m)
-- NOTE: we explicitly hide shadowing errors here, by using shadowNames'
decls' <- shadowNames' CheckOverlap env (traverse rename (mDecls m))
return (env,m { mDecls = decls' })
instance Rename TopDecl where
rename td = case td of
Decl d -> Decl <$> traverse rename d
TDNewtype n -> TDNewtype <$> traverse rename n
Include n -> return (Include n)
rnLocated :: (a -> RenameM b) -> Located a -> RenameM (Located b)
rnLocated f loc = withLoc loc $
do a' <- f (thing loc)
return loc { thing = a' }
instance Rename Decl where
rename d = case d of
DSignature ns sig -> DSignature <$> traverse (rnLocated renameVar) ns
<*> rename sig
DPragma ns p -> DPragma <$> traverse (rnLocated renameVar) ns
<*> pure p
DBind b -> DBind <$> rename b
-- XXX we probably shouldn't see these at this point...
DPatBind pat e -> do (pe,[pat']) <- renamePats [pat]
shadowNames pe (DPatBind pat' <$> rename e)
DType syn -> DType <$> rename syn
DLocated d' r -> withLoc r
$ DLocated <$> rename d' <*> pure r
DFixity{} -> panic "Renamer" ["Unexpected fixity declaration"
, show d]
instance Rename Newtype where
rename n = do
name' <- rnLocated renameType (nName n)
shadowNames (nParams n) $
do ps' <- traverse rename (nParams n)
body' <- traverse (rnNamed rename) (nBody n)
return Newtype { nName = name'
, nParams = ps'
, nBody = body' }
renameVar :: PName -> RenameM Name
renameVar qn = do
ro <- RenameM ask
case Map.lookup qn (neExprs (roNames ro)) of
Just [n] -> return n
Just [] -> panic "Renamer" ["Invalid expression renaming environment"]
Just syms ->
do n <- located qn
record (MultipleSyms n syms)
return (head syms)
-- This is an unbound value. Record an error and invent a bogus real name
-- for it.
Nothing ->
do n <- located qn
case Map.lookup qn (neTypes (roNames ro)) of
-- types existed with the name of the value expected
Just _ -> record (ExpectedValue n)
-- the value is just missing
Nothing -> record (UnboundExpr n)
mkFakeName qn
-- | Produce a name if one exists. Note that this includes situations where
-- overlap exists, as it's just a query about anything being in scope. In the
-- event that overlap does exist, an error will be recorded.
typeExists :: PName -> RenameM (Maybe Name)
typeExists pn =
do ro <- RenameM ask
case Map.lookup pn (neTypes (roNames ro)) of
Just [n] -> return (Just n)
Just [] -> panic "Renamer" ["Invalid type renaming environment"]
Just syms -> do n <- located pn
record (MultipleSyms n syms)
return (Just (head syms))
Nothing -> return Nothing
renameType :: PName -> RenameM Name
renameType pn =
do mb <- typeExists pn
case mb of
Just n -> return n
-- This is an unbound value. Record an error and invent a bogus real name
-- for it.
Nothing ->
do ro <- RenameM ask
let n = Located { srcRange = roLoc ro, thing = pn }
case Map.lookup pn (neExprs (roNames ro)) of
-- values exist with the same name, so throw a different error
Just _ -> record (ExpectedType n)
-- no terms with the same name, so the type is just unbound
Nothing -> record (UnboundType n)
mkFakeName pn
-- | Assuming an error has been recorded already, construct a fake name that's
-- not expected to make it out of the renamer.
mkFakeName :: PName -> RenameM Name
mkFakeName pn =
do ro <- RenameM ask
liftSupply (mkParameter (getIdent pn) (roLoc ro))
-- | Rename a schema, assuming that none of its type variables are already in
-- scope.
instance Rename Schema where
rename s = snd `fmap` renameSchema s
-- | Rename a schema, assuming that the type variables have already been brought
-- into scope.
renameSchema :: Schema PName -> RenameM (NamingEnv,Schema Name)
renameSchema (Forall ps p ty loc) =
do -- check that the parameters don't shadow any built-in types
let reserved = filter (isReserved . tpName) ps
mkErr tp = BoundReservedType (tpName tp) (tpRange tp) (text "schema")
unless (null reserved) (mapM_ (record . mkErr) reserved)
env <- liftSupply (namingEnv' ps)
s' <- shadowNames env $ Forall <$> traverse rename ps
<*> traverse rename p
<*> rename ty
<*> pure loc
return (env,s')
instance Rename TParam where
rename TParam { .. } =
do n <- renameType tpName
return TParam { tpName = n, .. }
instance Rename Prop where
rename p = case p of
CFin t -> CFin <$> rename t
CEqual l r -> CEqual <$> rename l <*> rename r
CGeq l r -> CGeq <$> rename l <*> rename r
CArith t -> CArith <$> rename t
CCmp t -> CCmp <$> rename t
CLocated p' r -> withLoc r
$ CLocated <$> rename p' <*> pure r
-- here, we rename the type and then require that it produces something that
-- looks like a Prop
CType t -> translateProp =<< resolveTypeFixity t
translateProp :: Type PName -> RenameM (Prop Name)
translateProp ty = go ty
where
go t = case t of
TLocated t' r -> (`CLocated` r) <$> go t'
-- these are the only cases that will produce valid props.
TUser n [l,r]
| i == packIdent "==" -> CEqual <$> rename l <*> rename r
| i == packIdent ">=" -> CGeq <$> rename l <*> rename r
| i == packIdent "<=" -> CGeq <$> rename r <*> rename l
where
i = getIdent n
-- record an error, but continue renaming to gather any other errors
_ ->
do record (InvalidConstraint ty)
CType <$> rename t
-- | Check to see if this identifier is a reserved type/type-function.
isReserved :: PName -> Bool
isReserved pn = Map.member pn tfunNames || isReservedTyCon pn
isReservedTyCon :: PName -> Bool
isReservedTyCon pn = Map.member pn tconNames
-- | Resolve fixity, then rename the resulting type.
instance Rename Type where
rename ty0 = go =<< resolveTypeFixity ty0
where
go :: Type PName -> RenameM (Type Name)
go (TFun a b) = TFun <$> go a <*> go b
go (TSeq n a) = TSeq <$> go n <*> go a
go TBit = return TBit
go (TNum c) = return (TNum c)
go (TChar c) = return (TChar c)
go TInf = return TInf
go (TUser pn ps)
-- all type functions
| Just (arity,fun) <- Map.lookup pn tfunNames =
do when (arity /= length ps) (record (MalformedBuiltin ty0 pn))
ps' <- traverse go ps
return (TApp fun ps')
-- built-in types like Bit and inf
| Just ty <- Map.lookup pn tconNames =
rename ty
go (TUser qn ps) = TUser <$> renameType qn <*> traverse go ps
go (TApp f xs) = TApp f <$> traverse go xs
go (TRecord fs) = TRecord <$> traverse (rnNamed go) fs
go (TTuple fs) = TTuple <$> traverse go fs
go TWild = return TWild
go (TLocated t' r) = withLoc r (TLocated <$> go t' <*> pure r)
go (TParens t') = TParens <$> go t'
-- at this point, the fixity is correct, and we just need to perform
-- renaming.
go (TInfix a o f b) = TInfix <$> rename a
<*> rnLocated renameType o
<*> pure f
<*> rename b
resolveTypeFixity :: Type PName -> RenameM (Type PName)
resolveTypeFixity = go
where
go t = case t of
TFun a b -> TFun <$> go a <*> go b
TSeq n a -> TSeq <$> go n <*> go a
TUser pn ps -> TUser pn <$> traverse go ps
TApp f xs -> TApp f <$> traverse go xs
TRecord fs -> TRecord <$> traverse (traverse go) fs
TTuple fs -> TTuple <$> traverse go fs
TLocated t' r-> withLoc r (TLocated <$> go t' <*> pure r)
TParens t' -> TParens <$> go t'
TInfix a o _ b ->
do let op = lookupFixity o
a' <- go a
b' <- go b
mkTInfix a' op b'
TBit -> return t
TNum _ -> return t
TChar _ -> return t
TInf -> return t
TWild -> return t
type TOp = Type PName -> Type PName -> Type PName
infixProps :: [PName]
infixProps = map (mkUnqual . packInfix) [ "==", ">=", "<=" ]
mkTInfix :: Type PName -> (TOp,Fixity) -> Type PName -> RenameM (Type PName)
-- only if the function is one of props
mkTInfix t@(TUser o1 [x,y]) op@(o2,f2) z
| o1 `elem` infixProps =
do let f1 = Fixity NonAssoc 0
case compareFixity f1 f2 of
FCLeft -> return (o2 t z)
FCRight -> do r <- mkTInfix y op z
return (TUser o1 [x,r])
-- Just reconstruct with the TUser part being an application. If this was
-- a real error, it will be caught during renaming.
FCError -> return (o2 t z)
-- In this case, we know the fixities of both sides.
mkTInfix t@(TApp o1 [x,y]) op@(o2,f2) z
| Just (a1,p1) <- Map.lookup o1 tBinOpPrec =
case compareFixity (Fixity a1 p1) f2 of
FCLeft -> return (o2 t z)
FCRight -> do r <- mkTInfix y op z
return (TApp o1 [x,r])
-- As the fixity table is known, and this is a case where the fixity came
-- from that table, it's a real error if the fixities didn't work out.
FCError -> panic "Renamer" [ "fixity problem for type operators"
, show (o2 t z) ]
mkTInfix (TLocated t _) op z =
mkTInfix t op z
mkTInfix t (op,_) z =
return (op t z)
-- | When possible, rewrite the type operator to a known constructor, otherwise
-- return a 'TOp' that reconstructs the original term, and a default fixity.
lookupFixity :: Located PName -> (TOp,Fixity)
lookupFixity op =
case lkp of
Just (p,f) -> (\x y -> TApp p [x,y], f)
-- unknown type operator, just use default fixity
-- NOTE: this works for the props defined above, as all other operators
-- are defined with a higher precedence.
Nothing -> (\x y -> TUser sym [x,y], Fixity NonAssoc 0)
where
sym = thing op
lkp = do (_,n) <- Map.lookup (thing op) tfunNames
(fAssoc,fLevel) <- Map.lookup n tBinOpPrec
return (n,Fixity { .. })
-- | Rename a binding.
instance Rename Bind where
rename b = do
n' <- rnLocated renameVar (bName b)
mbSig <- traverse renameSchema (bSignature b)
shadowNames (fst `fmap` mbSig) $
do (patEnv,pats') <- renamePats (bParams b)
-- NOTE: renamePats will generate warnings, so we don't need to trigger
-- them again here.
e' <- shadowNames' CheckNone patEnv (rnLocated rename (bDef b))
return b { bName = n'
, bParams = pats'
, bDef = e'
, bSignature = snd `fmap` mbSig
, bPragmas = bPragmas b
}
instance Rename BindDef where
rename DPrim = return DPrim
rename (DExpr e) = DExpr <$> rename e
-- NOTE: this only renames types within the pattern.
instance Rename Pattern where
rename p = case p of
PVar lv -> PVar <$> rnLocated renameVar lv
PWild -> pure PWild
PTuple ps -> PTuple <$> traverse rename ps
PRecord nps -> PRecord <$> traverse (rnNamed rename) nps
PList elems -> PList <$> traverse rename elems
PTyped p' t -> PTyped <$> rename p' <*> rename t
PSplit l r -> PSplit <$> rename l <*> rename r
PLocated p' loc -> withLoc loc
$ PLocated <$> rename p' <*> pure loc
instance Rename Expr where
rename e = case e of
EVar n -> EVar <$> renameVar n
ELit l -> return (ELit l)
ETuple es -> ETuple <$> traverse rename es
ERecord fs -> ERecord <$> traverse (rnNamed rename) fs
ESel e' s -> ESel <$> rename e' <*> pure s
EList es -> EList <$> traverse rename es
EFromTo s n e'-> EFromTo <$> rename s
<*> traverse rename n
<*> traverse rename e'
EInfFrom a b -> EInfFrom<$> rename a <*> traverse rename b
EComp e' bs -> do arms' <- traverse renameArm bs
let (envs,bs') = unzip arms'
-- NOTE: renameArm will generate shadowing warnings; we only
-- need to check for repeated names across multiple arms
shadowNames' CheckOverlap envs (EComp <$> rename e' <*> pure bs')
EApp f x -> EApp <$> rename f <*> rename x
EAppT f ti -> EAppT <$> rename f <*> traverse rename ti
EIf b t f -> EIf <$> rename b <*> rename t <*> rename f
EWhere e' ds -> do ns <- getNS
shadowNames (map (InModule ns) ds) $
EWhere <$> rename e' <*> traverse rename ds
ETyped e' ty -> ETyped <$> rename e' <*> rename ty
ETypeVal ty -> ETypeVal<$> rename ty
EFun ps e' -> do (env,ps') <- renamePats ps
-- NOTE: renamePats will generate warnings, so we don't
-- need to duplicate them here
shadowNames' CheckNone env (EFun ps' <$> rename e')
ELocated e' r -> withLoc r
$ ELocated <$> rename e' <*> pure r
EParens p -> EParens <$> rename p
EInfix x y _ z-> do op <- renameOp y
x' <- rename x
z' <- rename z
mkEInfix x' op z'
mkEInfix :: Expr Name -- ^ May contain infix expressions
-> (Located Name,Fixity) -- ^ The operator to use
-> Expr Name -- ^ Will not contain infix expressions
-> RenameM (Expr Name)
mkEInfix e@(EInfix x o1 f1 y) op@(o2,f2) z =
case compareFixity f1 f2 of
FCLeft -> return (EInfix e o2 f2 z)
FCRight -> do r <- mkEInfix y op z
return (EInfix x o1 f1 r)
FCError -> do record (FixityError o1 o2)
return (EInfix e o2 f2 z)
mkEInfix (ELocated e' _) op z =
mkEInfix e' op z
mkEInfix e (o,f) z =
return (EInfix e o f z)
renameOp :: Located PName -> RenameM (Located Name,Fixity)
renameOp ln = withLoc ln $
do n <- renameVar (thing ln)
ro <- RenameM ask
case Map.lookup n (neFixity (roNames ro)) of
Just fixity -> return (ln { thing = n },fixity)
Nothing -> return (ln { thing = n },defaultFixity)
instance Rename TypeInst where
rename ti = case ti of
NamedInst nty -> NamedInst <$> traverse rename nty
PosInst ty -> PosInst <$> rename ty
renameArm :: [Match PName] -> RenameM (NamingEnv,[Match Name])
renameArm (m:ms) =
do (me,m') <- renameMatch m
-- NOTE: renameMatch will generate warnings, so we don't
-- need to duplicate them here
shadowNames' CheckNone me $
do (env,rest) <- renameArm ms
-- NOTE: the inner environment shadows the outer one, for examples
-- like this:
--
-- [ x | x <- xs, let x = 10 ]
return (env `shadowing` me, m':rest)
renameArm [] =
return (mempty,[])
-- | The name environment generated by a single match.
renameMatch :: Match PName -> RenameM (NamingEnv,Match Name)
renameMatch (Match p e) =
do (pe,[p']) <- renamePats [p]
e' <- rename e
return (pe,Match p' e')
renameMatch (MatchLet b) =
do ns <- getNS
be <- liftSupply (namingEnv' (InModule ns b))
b' <- shadowNames be (rename b)
return (be,MatchLet b')
-- | Rename patterns, and collect the new environment that they introduce.
renamePats :: [Pattern PName] -> RenameM (NamingEnv,[Pattern Name])
renamePats = loop
where
loop ps = case ps of
p:rest -> do
pe <- patternEnv p
shadowNames pe $
do p' <- rename p
(env',rest') <- loop rest
return (pe `mappend` env', p':rest')
[] -> return (mempty, [])
patternEnv :: Pattern PName -> RenameM NamingEnv
patternEnv = go
where
go (PVar Located { .. }) =
do n <- liftSupply (mkParameter (getIdent thing) srcRange)
return (singletonE thing n)
go PWild = return mempty
go (PTuple ps) = bindVars ps
go (PRecord fs) = bindVars (map value fs)
go (PList ps) = foldMap go ps
go (PTyped p ty) = go p `mappend` typeEnv ty
go (PSplit a b) = go a `mappend` go b
go (PLocated p loc) = withLoc loc (go p)
bindVars [] = return mempty
bindVars (p:ps) =
do env <- go p
shadowNames env $
do rest <- bindVars ps
return (env `mappend` rest)
typeEnv (TFun a b) = bindTypes [a,b]
typeEnv (TSeq a b) = bindTypes [a,b]
typeEnv TBit = return mempty
typeEnv TNum{} = return mempty
typeEnv TChar{} = return mempty
typeEnv TInf = return mempty
typeEnv (TUser pn ps) =
do mb <- typeExists pn
case mb of
-- The type is already bound, don't introduce anything.
Just _ -> bindTypes ps
Nothing
-- Just ignore reserved names, as they'll be resolved when renaming.
| isReserved pn ->
bindTypes ps
-- The type isn't bound, and has no parameters, so it names a portion
-- of the type of the pattern.
| null ps ->
do loc <- curLoc
n <- liftSupply (mkParameter (getIdent pn) loc)
return (singletonT pn n)
-- This references a type synonym that's not in scope. Record an
-- error and continue with a made up name.
| otherwise ->
do loc <- curLoc
record (UnboundType (Located loc pn))
n <- liftSupply (mkParameter (getIdent pn) loc)
return (singletonT pn n)
typeEnv (TApp _ ts) = bindTypes ts
typeEnv (TRecord fs) = bindTypes (map value fs)
typeEnv (TTuple ts) = bindTypes ts
typeEnv TWild = return mempty
typeEnv (TLocated ty loc) = withLoc loc (typeEnv ty)
typeEnv (TParens ty) = typeEnv ty
typeEnv (TInfix a _ _ b) = bindTypes [a,b]
bindTypes [] = return mempty
bindTypes (t:ts) =
do env' <- typeEnv t
shadowNames env' $
do res <- bindTypes ts
return (env' `mappend` res)
instance Rename Match where
rename m = case m of
Match p e -> Match <$> rename p <*> rename e
MatchLet b -> shadowNamesNS b (MatchLet <$> rename b)
instance Rename TySyn where
rename (TySyn n ps ty) =
do when (isReserved (thing n))
(record (BoundReservedType (thing n) (getLoc n) (text "type synonym")))
shadowNames ps $ TySyn <$> rnLocated renameType n
<*> traverse rename ps
<*> rename ty
-- Utilities -------------------------------------------------------------------
rnNamed :: (a -> RenameM b) -> Named a -> RenameM (Named b)
rnNamed = traverse
{-# INLINE rnNamed #-}
cryptol-2.4.0/src/Cryptol/Parser/ 0000755 0000000 0000000 00000000000 12737220176 015065 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Parser/AST.hs 0000644 0000000 0000000 00000102410 12737220176 016046 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.Parser.AST
( -- * Names
Ident, mkIdent, mkInfix, isInfixIdent, nullIdent, identText
, ModName, modRange
, PName(..), getModName, getIdent, mkUnqual, mkQual
, Named(..)
, Pass(..)
, Assoc(..)
-- * Types
, Schema(..)
, TParam(..)
, Kind(..)
, Type(..), tconNames
, Prop(..)
-- * Declarations
, Module(..)
, Program(..)
, TopDecl(..)
, Decl(..)
, Fixity(..), defaultFixity
, FixityCmp(..), compareFixity
, TySyn(..)
, Bind(..)
, BindDef(..), LBindDef
, Pragma(..)
, ExportType(..)
, ExportSpec(..), exportBind, exportType
, isExportedBind, isExportedType
, TopLevel(..)
, Import(..), ImportSpec(..)
, Newtype(..)
-- * Interactive
, ReplInput(..)
-- * Expressions
, Expr(..)
, Literal(..), NumInfo(..)
, Match(..)
, Pattern(..)
, Selector(..)
, TypeInst(..)
-- * Positions
, Located(..)
, LPName, LString, LIdent
, NoPos(..)
-- * Pretty-printing
, cppKind, ppSelector
) where
import Cryptol.Parser.Name
import Cryptol.Parser.Position
import Cryptol.Prims.Syntax (TFun(..))
import Cryptol.Utils.Ident
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import qualified Data.Set as Set
import Data.List(intersperse)
import Data.Bits(shiftR)
import Data.Maybe (catMaybes)
import qualified Data.Map as Map
import Numeric(showIntAtBase)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- AST -------------------------------------------------------------------------
-- | A name with location information.
type LPName = Located PName
-- | An identifier with location information.
type LIdent = Located Ident
-- | A string with location information.
type LString = Located String
newtype Program name = Program [TopDecl name]
deriving (Show)
data Module name = Module { mName :: Located ModName
, mImports :: [Located Import]
, mDecls :: [TopDecl name]
} deriving (Show, Generic, NFData)
modRange :: Module name -> Range
modRange m = rCombs $ catMaybes
[ getLoc (mName m)
, getLoc (mImports m)
, getLoc (mDecls m)
, Just (Range { from = start, to = start, source = "" })
]
data TopDecl name = Decl (TopLevel (Decl name))
| TDNewtype (TopLevel (Newtype name))
| Include (Located FilePath)
deriving (Show, Generic, NFData)
data Decl name = DSignature [Located name] (Schema name)
| DFixity !Fixity [Located name]
| DPragma [Located name] Pragma
| DBind (Bind name)
| DPatBind (Pattern name) (Expr name)
| DType (TySyn name)
| DLocated (Decl name) Range
deriving (Eq, Show, Generic, NFData)
-- | An import declaration.
data Import = Import { iModule :: !ModName
, iAs :: Maybe ModName
, iSpec :: Maybe ImportSpec
} deriving (Eq, Show, Generic, NFData)
-- | The list of names following an import.
--
-- INVARIANT: All of the 'Name' entries in the list are expected to be
-- unqualified names; the 'QName' or 'NewName' constructors should not be
-- present.
data ImportSpec = Hiding [Ident]
| Only [Ident]
deriving (Eq, Show, Generic, NFData)
data TySyn n = TySyn (Located n) [TParam n] (Type n)
deriving (Eq, Show, Generic, NFData)
{- | Bindings. Notes:
* The parser does not associate type signatures and pragmas with
their bindings: this is done in a separate pass, after de-sugaring
pattern bindings. In this way we can associate pragmas and type
signatures with the variables defined by pattern bindings as well.
* Currently, there is no surface syntax for defining monomorphic
bindings (i.e., bindings that will not be automatically generalized
by the type checker. However, they are useful when de-sugaring
patterns.
-}
data Bind name = Bind { bName :: Located name -- ^ Defined thing
, bParams :: [Pattern name]-- ^ Parameters
, bDef :: Located (BindDef name) -- ^ Definition
, bSignature :: Maybe (Schema name) -- ^ Optional type sig
, bInfix :: Bool -- ^ Infix operator?
, bFixity :: Maybe Fixity -- ^ Optional fixity info
, bPragmas :: [Pragma] -- ^ Optional pragmas
, bMono :: Bool -- ^ Is this a monomorphic binding
, bDoc :: Maybe String -- ^ Optional doc string
} deriving (Eq, Show, Generic, NFData)
type LBindDef = Located (BindDef PName)
data BindDef name = DPrim
| DExpr (Expr name)
deriving (Eq, Show, Generic, NFData)
data Fixity = Fixity { fAssoc :: !Assoc
, fLevel :: !Int
} deriving (Eq, Show, Generic, NFData)
data FixityCmp = FCError
| FCLeft
| FCRight
deriving (Show,Eq)
compareFixity :: Fixity -> Fixity -> FixityCmp
compareFixity (Fixity a1 p1) (Fixity a2 p2) =
case compare p1 p2 of
GT -> FCLeft
LT -> FCRight
EQ -> case (a1,a2) of
(LeftAssoc,LeftAssoc) -> FCLeft
(RightAssoc,RightAssoc) -> FCRight
_ -> FCError
-- | The fixity used when none is provided.
defaultFixity :: Fixity
defaultFixity = Fixity LeftAssoc 100
data Pragma = PragmaNote String
| PragmaProperty
deriving (Eq, Show, Generic, NFData)
data Newtype name = Newtype { nName :: Located name -- ^ Type name
, nParams :: [TParam name] -- ^ Type params
, nBody :: [Named (Type name)] -- ^ Constructor
} deriving (Eq, Show, Generic, NFData)
-- | Input at the REPL, which can either be an expression or a @let@
-- statement.
data ReplInput name = ExprInput (Expr name)
| LetInput (Decl name)
deriving (Eq, Show)
-- | Export information for a declaration.
data ExportType = Public
| Private
deriving (Eq, Show, Ord, Generic, NFData)
data TopLevel a = TopLevel { tlExport :: ExportType
, tlDoc :: Maybe (Located String)
, tlValue :: a
}
deriving (Show, Generic, NFData, Functor, Foldable, Traversable)
data ExportSpec name = ExportSpec { eTypes :: Set.Set name
, eBinds :: Set.Set name
} deriving (Show, Generic, NFData)
instance Ord name => Monoid (ExportSpec name) where
mempty = ExportSpec { eTypes = mempty, eBinds = mempty }
mappend l r = ExportSpec { eTypes = mappend (eTypes l) (eTypes r)
, eBinds = mappend (eBinds l) (eBinds r)
}
-- | Add a binding name to the export list, if it should be exported.
exportBind :: Ord name => TopLevel name -> ExportSpec name
exportBind n
| tlExport n == Public = mempty { eBinds = Set.singleton (tlValue n) }
| otherwise = mempty
-- | Check to see if a binding is exported.
isExportedBind :: Ord name => name -> ExportSpec name -> Bool
isExportedBind n = Set.member n . eBinds
-- | Add a type synonym name to the export list, if it should be exported.
exportType :: Ord name => TopLevel name -> ExportSpec name
exportType n
| tlExport n == Public = mempty { eTypes = Set.singleton (tlValue n) }
| otherwise = mempty
-- | Check to see if a type synonym is exported.
isExportedType :: Ord name => name -> ExportSpec name -> Bool
isExportedType n = Set.member n . eTypes
-- | Infromation about the representation of a numeric constant.
data NumInfo = BinLit Int -- ^ n-digit binary literal
| OctLit Int -- ^ n-digit octal literal
| DecLit -- ^ overloaded decimal literal
| HexLit Int -- ^ n-digit hex literal
| CharLit -- ^ character literal
| PolyLit Int -- ^ polynomial literal
deriving (Eq, Show, Generic, NFData)
-- | Literals.
data Literal = ECNum Integer NumInfo -- ^ @0x10@ (HexLit 2)
| ECString String -- ^ @\"hello\"@
deriving (Eq, Show, Generic, NFData)
data Expr n = EVar n -- ^ @ x @
| ELit Literal -- ^ @ 0x10 @
| ETuple [Expr n] -- ^ @ (1,2,3) @
| ERecord [Named (Expr n)] -- ^ @ { x = 1, y = 2 } @
| ESel (Expr n) Selector -- ^ @ e.l @
| EList [Expr n] -- ^ @ [1,2,3] @
| EFromTo (Type n) (Maybe (Type n)) (Maybe (Type n)) -- ^ @[1, 5 .. 117 ] @
| EInfFrom (Expr n) (Maybe (Expr n))-- ^ @ [1, 3 ...] @
| EComp (Expr n) [[Match n]] -- ^ @ [ 1 | x <- xs ] @
| EApp (Expr n) (Expr n) -- ^ @ f x @
| EAppT (Expr n) [(TypeInst n)] -- ^ @ f `{x = 8}, f`{8} @
| EIf (Expr n) (Expr n) (Expr n) -- ^ @ if ok then e1 else e2 @
| EWhere (Expr n) [Decl n] -- ^ @ 1 + x where { x = 2 } @
| ETyped (Expr n) (Type n) -- ^ @ 1 : [8] @
| ETypeVal (Type n) -- ^ @ `(x + 1)@, @x@ is a type
| EFun [Pattern n] (Expr n) -- ^ @ \\x y -> x @
| ELocated (Expr n) Range -- ^ position annotation
| EParens (Expr n) -- ^ @ (e) @ (Removed by Fixity)
| EInfix (Expr n) (Located n) Fixity (Expr n)-- ^ @ a + b @ (Removed by Fixity)
deriving (Eq, Show, Generic, NFData)
data TypeInst name = NamedInst (Named (Type name))
| PosInst (Type name)
deriving (Eq, Show, Generic, NFData)
{- | Selectors are used for projecting from various components.
Each selector has an option spec to specify the shape of the thing
that is being selected. Currently, there is no surface syntax for
list selectors, but they are used during the desugaring of patterns.
-}
data Selector = TupleSel Int (Maybe Int)
-- ^ Zero-based tuple selection.
-- Optionally specifies the shape of the tuple (one-based).
| RecordSel Ident (Maybe [Ident])
-- ^ Record selection.
-- Optionally specifies the shape of the record.
| ListSel Int (Maybe Int)
-- ^ List selection.
-- Optionally specifies the length of the list.
deriving (Eq, Show, Ord, Generic, NFData)
data Match name = Match (Pattern name) (Expr name) -- ^ p <- e
| MatchLet (Bind name)
deriving (Eq, Show, Generic, NFData)
data Pattern n = PVar (Located n) -- ^ @ x @
| PWild -- ^ @ _ @
| PTuple [Pattern n] -- ^ @ (x,y,z) @
| PRecord [ Named (Pattern n) ] -- ^ @ { x = (a,b,c), y = z } @
| PList [ Pattern n ] -- ^ @ [ x, y, z ] @
| PTyped (Pattern n) (Type n) -- ^ @ x : [8] @
| PSplit (Pattern n) (Pattern n)-- ^ @ (x # y) @
| PLocated (Pattern n) Range -- ^ Location information
deriving (Eq, Show, Generic, NFData)
data Named a = Named { name :: Located Ident, value :: a }
deriving (Eq, Show, Foldable, Traversable, Generic, NFData, Functor)
data Schema n = Forall [TParam n] [Prop n] (Type n) (Maybe Range)
deriving (Eq, Show, Generic, NFData)
data Kind = KNum | KType
deriving (Eq, Show, Generic, NFData)
data TParam n = TParam { tpName :: n
, tpKind :: Maybe Kind
, tpRange :: Maybe Range
}
deriving (Eq, Show, Generic, NFData)
data Type n = TFun (Type n) (Type n) -- ^ @[8] -> [8]@
| TSeq (Type n) (Type n) -- ^ @[8] a@
| TBit -- ^ @Bit@
| TNum Integer -- ^ @10@
| TChar Char -- ^ @'a'@
| TInf -- ^ @inf@
| TUser n [Type n] -- ^ A type variable or synonym
| TApp TFun [Type n] -- ^ @2 + x@
| TRecord [Named (Type n)]-- ^ @{ x : [8], y : [32] }@
| TTuple [Type n] -- ^ @([8], [32])@
| TWild -- ^ @_@, just some type.
| TLocated (Type n) Range -- ^ Location information
| TParens (Type n) -- ^ @ (ty) @
| TInfix (Type n) (Located n) Fixity (Type n) -- ^ @ ty + ty @
deriving (Eq, Show, Generic, NFData)
tconNames :: Map.Map PName (Type PName)
tconNames = Map.fromList
[ (mkUnqual (packIdent "Bit"), TBit)
, (mkUnqual (packIdent "inf"), TInf)
]
data Prop n = CFin (Type n) -- ^ @ fin x @
| CEqual (Type n) (Type n) -- ^ @ x == 10 @
| CGeq (Type n) (Type n) -- ^ @ x >= 10 @
| CArith (Type n) -- ^ @ Arith a @
| CCmp (Type n) -- ^ @ Cmp a @
| CLocated (Prop n) Range -- ^ Location information
| CType (Type n) -- ^ After parsing
deriving (Eq, Show, Generic, NFData)
--------------------------------------------------------------------------------
-- Note: When an explicit location is missing, we could use the sub-components
-- to try to estimate a location...
instance AddLoc (Expr n) where
addLoc = ELocated
dropLoc (ELocated e _) = dropLoc e
dropLoc e = e
instance HasLoc (Expr name) where
getLoc (ELocated _ r) = Just r
getLoc _ = Nothing
instance HasLoc (TParam name) where
getLoc (TParam _ _ r) = r
instance AddLoc (TParam name) where
addLoc (TParam a b _) l = TParam a b (Just l)
dropLoc (TParam a b _) = TParam a b Nothing
instance HasLoc (Type name) where
getLoc (TLocated _ r) = Just r
getLoc _ = Nothing
instance AddLoc (Type name) where
addLoc = TLocated
dropLoc (TLocated e _) = dropLoc e
dropLoc e = e
instance HasLoc (Prop name) where
getLoc (CLocated _ r) = Just r
getLoc _ = Nothing
instance AddLoc (Prop name) where
addLoc = CLocated
dropLoc (CLocated e _) = dropLoc e
dropLoc e = e
instance AddLoc (Pattern name) where
addLoc = PLocated
dropLoc (PLocated e _) = dropLoc e
dropLoc e = e
instance HasLoc (Pattern name) where
getLoc (PLocated _ r) = Just r
getLoc (PTyped r _) = getLoc r
getLoc (PVar x) = getLoc x
getLoc _ = Nothing
instance HasLoc (Bind name) where
getLoc b = getLoc (bName b, bDef b)
instance HasLoc (Match name) where
getLoc (Match p e) = getLoc (p,e)
getLoc (MatchLet b) = getLoc b
instance HasLoc a => HasLoc (Named a) where
getLoc l = getLoc (name l, value l)
instance HasLoc (Schema name) where
getLoc (Forall _ _ _ r) = r
instance AddLoc (Schema name) where
addLoc (Forall xs ps t _) r = Forall xs ps t (Just r)
dropLoc (Forall xs ps t _) = Forall xs ps t Nothing
instance HasLoc (Decl name) where
getLoc (DLocated _ r) = Just r
getLoc _ = Nothing
instance AddLoc (Decl name) where
addLoc d r = DLocated d r
dropLoc (DLocated d _) = dropLoc d
dropLoc d = d
instance HasLoc a => HasLoc (TopLevel a) where
getLoc = getLoc . tlValue
instance HasLoc (TopDecl name) where
getLoc td = case td of
Decl tld -> getLoc tld
TDNewtype n -> getLoc n
Include lfp -> getLoc lfp
instance HasLoc (Module name) where
getLoc m
| null locs = Nothing
| otherwise = Just (rCombs locs)
where
locs = catMaybes [ getLoc (mName m)
, getLoc (mImports m)
, getLoc (mDecls m)
]
instance HasLoc (Newtype name) where
getLoc n
| null locs = Nothing
| otherwise = Just (rCombs locs)
where
locs = catMaybes [ getLoc (nName n), getLoc (nBody n) ]
--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- Pretty printing
ppL :: PP a => Located a -> Doc
ppL = pp . thing
ppNamed :: PP a => String -> Named a -> Doc
ppNamed s x = ppL (name x) <+> text s <+> pp (value x)
instance (Show name, PPName name) => PP (Module name) where
ppPrec _ m = text "module" <+> ppL (mName m) <+> text "where"
$$ vcat (map ppL (mImports m))
$$ vcat (map pp (mDecls m))
instance (Show name, PPName name) => PP (Program name) where
ppPrec _ (Program ds) = vcat (map pp ds)
instance (Show name, PPName name) => PP (TopDecl name) where
ppPrec _ top_decl =
case top_decl of
Decl d -> pp d
TDNewtype n -> pp n
Include l -> text "include" <+> text (show (thing l))
instance (Show name, PPName name) => PP (Decl name) where
ppPrec n decl =
case decl of
DSignature xs s -> commaSep (map ppL xs) <+> text ":" <+> pp s
DPatBind p e -> pp p <+> text "=" <+> pp e
DBind b -> ppPrec n b
DFixity f ns -> ppFixity f ns
DPragma xs p -> ppPragma xs p
DType ts -> ppPrec n ts
DLocated d _ -> ppPrec n d
ppFixity :: PPName name => Fixity -> [Located name] -> Doc
ppFixity (Fixity LeftAssoc i) ns = text "infixl" <+> int i <+> commaSep (map pp ns)
ppFixity (Fixity RightAssoc i) ns = text "infixr" <+> int i <+> commaSep (map pp ns)
ppFixity (Fixity NonAssoc i) ns = text "infix" <+> int i <+> commaSep (map pp ns)
instance PPName name => PP (Newtype name) where
ppPrec _ nt = hsep
[ text "newtype", ppL (nName nt), hsep (map pp (nParams nt)), char '='
, braces (commaSep (map (ppNamed ":") (nBody nt))) ]
instance PP Import where
ppPrec _ d = text "import" <+> sep [ pp (iModule d), mbAs, mbSpec ]
where
mbAs = maybe empty (\ name -> text "as" <+> pp name ) (iAs d)
mbSpec = maybe empty pp (iSpec d)
instance PP ImportSpec where
ppPrec _ s = case s of
Hiding names -> text "hiding" <+> parens (commaSep (map pp names))
Only names -> parens (commaSep (map pp names))
-- TODO: come up with a good way of showing the export specification here
instance PP a => PP (TopLevel a) where
ppPrec _ tl = pp (tlValue tl)
instance PP Pragma where
ppPrec _ (PragmaNote x) = text x
ppPrec _ PragmaProperty = text "property"
ppPragma :: PPName name => [Located name] -> Pragma -> Doc
ppPragma xs p =
text "/*" <+> text "pragma" <+> commaSep (map ppL xs) <+> text ":" <+> pp p
<+> text "*/"
instance (Show name, PPName name) => PP (Bind name) where
ppPrec _ b = sig $$ vcat [ ppPragma [f] p | p <- bPragmas b ] $$
hang (def <+> eq) 4 (pp (thing (bDef b)))
where def | bInfix b = lhsOp
| otherwise = lhs
f = bName b
sig = case bSignature b of
Nothing -> empty
Just s -> pp (DSignature [f] s)
eq = if bMono b then text ":=" else text "="
lhs = ppL f <+> fsep (map (ppPrec 3) (bParams b))
lhsOp = case bParams b of
[x,y] -> pp x <+> ppL f <+> pp y
_ -> panic "AST" [ "Malformed infix operator", show b ]
instance (Show name, PPName name) => PP (BindDef name) where
ppPrec _ DPrim = text ""
ppPrec p (DExpr e) = ppPrec p e
instance PPName name => PP (TySyn name) where
ppPrec _ (TySyn x xs t) = text "type" <+> ppL x <+> fsep (map (ppPrec 1) xs)
<+> text "=" <+> pp t
instance PP Literal where
ppPrec _ lit =
case lit of
ECNum n i -> ppNumLit n i
ECString s -> text (show s)
ppNumLit :: Integer -> NumInfo -> Doc
ppNumLit n info =
case info of
DecLit -> integer n
CharLit -> text (show (toEnum (fromInteger n) :: Char))
BinLit w -> pad 2 "0b" w
OctLit w -> pad 8 "0o" w
HexLit w -> pad 16 "0x" w
PolyLit w -> text "<|" <+> poly w <+> text "|>"
where
pad base pref w =
let txt = showIntAtBase base ("0123456789abcdef" !!) n ""
in text pref <> text (replicate (w - length txt) '0') <> text txt
poly w = let (res,deg) = bits Nothing [] 0 n
z | w == 0 = []
| Just d <- deg, d + 1 == w = []
| otherwise = [polyTerm0 (w-1)]
in fsep $ intersperse (text "+") $ z ++ map polyTerm res
polyTerm 0 = text "1"
polyTerm 1 = text "x"
polyTerm p = text "x" <> text "^^" <> int p
polyTerm0 0 = text "0"
polyTerm0 p = text "0" <> text "*" <> polyTerm p
bits d res p num
| num == 0 = (res,d)
| even num = bits d res (p + 1) (num `shiftR` 1)
| otherwise = bits (Just p) (p : res) (p + 1) (num `shiftR` 1)
wrap :: Int -> Int -> Doc -> Doc
wrap contextPrec myPrec doc = if myPrec < contextPrec then parens doc else doc
isEApp :: Expr n -> Maybe (Expr n, Expr n)
isEApp (ELocated e _) = isEApp e
isEApp (EApp e1 e2) = Just (e1,e2)
isEApp _ = Nothing
asEApps :: Expr n -> (Expr n, [Expr n])
asEApps expr = go expr []
where go e es = case isEApp e of
Nothing -> (e, es)
Just (e1, e2) -> go e1 (e2 : es)
instance PPName name => PP (TypeInst name) where
ppPrec _ (PosInst t) = pp t
ppPrec _ (NamedInst x) = ppNamed "=" x
{- Precedences:
0: lambda, if, where, type annotation
2: infix expression (separate precedence table)
3: application, prefix expressions
-}
instance (Show name, PPName name) => PP (Expr name) where
-- Wrap if top level operator in expression is less than `n`
ppPrec n expr =
case expr of
-- atoms
EVar x -> ppPrefixName x
ELit x -> pp x
ETuple es -> parens (commaSep (map pp es))
ERecord fs -> braces (commaSep (map (ppNamed "=") fs))
EList es -> brackets (commaSep (map pp es))
EFromTo e1 e2 e3 -> brackets (pp e1 <> step <+> text ".." <+> end)
where step = maybe empty (\e -> comma <+> pp e) e2
end = maybe empty pp e3
EInfFrom e1 e2 -> brackets (pp e1 <> step <+> text "...")
where step = maybe empty (\e -> comma <+> pp e) e2
EComp e mss -> brackets (pp e <+> vcat (map arm mss))
where arm ms = text "|" <+> commaSep (map pp ms)
ETypeVal t -> text "`" <> ppPrec 5 t -- XXX
EAppT e ts -> ppPrec 4 e <> text "`" <> braces (commaSep (map pp ts))
ESel e l -> ppPrec 4 e <> text "." <> pp l
-- low prec
EFun xs e -> wrap n 0 ((text "\\" <> hsep (map (ppPrec 3) xs)) <+>
text "->" <+> pp e)
EIf e1 e2 e3 -> wrap n 0 $ sep [ text "if" <+> pp e1
, text "then" <+> pp e2
, text "else" <+> pp e3 ]
ETyped e t -> wrap n 0 (ppPrec 2 e <+> text ":" <+> pp t)
EWhere e ds -> wrap n 0 (pp e
$$ text "where"
$$ nest 2 (vcat (map pp ds))
$$ text "")
-- infix applications
_ | Just ifix <- isInfix expr ->
optParens (n > 2)
$ ppInfix 2 isInfix ifix
EApp _ _ -> let (e, es) = asEApps expr in
wrap n 3 (ppPrec 3 e <+> fsep (map (ppPrec 4) es))
ELocated e _ -> ppPrec n e
EParens e -> parens (pp e)
EInfix e1 op _ e2 -> wrap n 0 (pp e1 <+> ppInfixName (thing op) <+> pp e2)
where
isInfix (EApp (EApp (EVar ieOp) ieLeft) ieRight) = do
(ieAssoc,iePrec) <- ppNameFixity ieOp
return Infix { .. }
isInfix _ = Nothing
instance PP Selector where
ppPrec _ sel =
case sel of
TupleSel x sig -> int x <+> ppSig tupleSig sig
RecordSel x sig -> pp x <+> ppSig recordSig sig
ListSel x sig -> int x <+> ppSig listSig sig
where
tupleSig n = int n
recordSig xs = braces $ fsep $ punctuate comma $ map pp xs
listSig n = int n
ppSig f = maybe empty (\x -> text "/* of" <+> f x <+> text "*/")
-- | Display the thing selected by the selector, nicely.
ppSelector :: Selector -> Doc
ppSelector sel =
case sel of
TupleSel x _ -> ordinal x <+> text "field"
RecordSel x _ -> text "field" <+> pp x
ListSel x _ -> ordinal x <+> text "element"
instance PPName name => PP (Pattern name) where
ppPrec n pat =
case pat of
PVar x -> pp (thing x)
PWild -> char '_'
PTuple ps -> parens (commaSep (map pp ps))
PRecord fs -> braces (commaSep (map (ppNamed "=") fs))
PList ps -> brackets (commaSep (map pp ps))
PTyped p t -> wrap n 0 (ppPrec 1 p <+> text ":" <+> pp t)
PSplit p1 p2 -> wrap n 1 (ppPrec 1 p1 <+> text "#" <+> ppPrec 1 p2)
PLocated p _ -> ppPrec n p
instance (Show name, PPName name) => PP (Match name) where
ppPrec _ (Match p e) = pp p <+> text "<-" <+> pp e
ppPrec _ (MatchLet b) = pp b
instance PPName name => PP (Schema name) where
ppPrec _ (Forall xs ps t _) = sep [vars <+> preds, pp t]
where vars = case xs of
[] -> empty
_ -> braces (commaSep (map pp xs))
preds = case ps of
[] -> empty
_ -> parens (commaSep (map pp ps)) <+> text "=>"
instance PP Kind where
ppPrec _ KType = text "*"
ppPrec _ KNum = text "#"
-- | "Conversational" printing of kinds (e.g., to use in error messages)
cppKind :: Kind -> Doc
cppKind KType = text "a value type"
cppKind KNum = text "a numeric type"
instance PPName name => PP (TParam name) where
ppPrec n (TParam p Nothing _) = ppPrec n p
ppPrec n (TParam p (Just k) _) = wrap n 1 (pp p <+> text ":" <+> pp k)
-- 4: wrap [_] t
-- 3: wrap application
-- 2: wrap function
-- 1:
instance PPName name => PP (Type name) where
ppPrec n ty =
case ty of
TWild -> text "_"
TTuple ts -> parens $ commaSep $ map pp ts
TRecord fs -> braces $ commaSep $ map (ppNamed ":") fs
TBit -> text "Bit"
TInf -> text "inf"
TNum x -> integer x
TChar x -> text (show x)
TSeq t1 TBit -> brackets (pp t1)
TSeq t1 t2 -> optParens (n > 3)
$ brackets (pp t1) <> ppPrec 3 t2
_ | Just tinf <- isInfix ty ->
optParens (n > 2)
$ ppInfix 2 isInfix tinf
TApp f ts -> optParens (n > 2)
$ pp f <+> fsep (map (ppPrec 4) ts)
TUser f [] -> ppPrefixName f
TUser f ts -> optParens (n > 2)
$ ppPrefixName f <+> fsep (map (ppPrec 4) ts)
TFun t1 t2 -> optParens (n > 1)
$ sep [ppPrec 2 t1 <+> text "->", ppPrec 1 t2]
TLocated t _ -> ppPrec n t
TParens t -> parens (pp t)
TInfix t1 o _ t2 -> optParens (n > 0)
$ sep [ppPrec 2 t1 <+> ppInfixName o, ppPrec 1 t2]
where
isInfix (TApp ieOp [ieLeft, ieRight]) = do
(ieAssoc,iePrec) <- ppNameFixity ieOp
return Infix { .. }
isInfix _ = Nothing
instance PPName name => PP (Prop name) where
ppPrec n prop =
case prop of
CFin t -> text "fin" <+> ppPrec 4 t
CArith t -> text "Arith" <+> ppPrec 4 t
CCmp t -> text "Cmp" <+> ppPrec 4 t
CEqual t1 t2 -> ppPrec 2 t1 <+> text "==" <+> ppPrec 2 t2
CGeq t1 t2 -> ppPrec 2 t1 <+> text ">=" <+> ppPrec 2 t2
CLocated c _ -> ppPrec n c
CType t -> ppPrec n t
--------------------------------------------------------------------------------
-- Drop all position information, so equality reflects program structure
class NoPos t where
noPos :: t -> t
-- WARNING: This does not call `noPos` on the `thing` inside
instance NoPos (Located t) where
noPos x = x { srcRange = rng }
where rng = Range { from = Position 0 0, to = Position 0 0, source = "" }
instance NoPos t => NoPos (Named t) where
noPos t = Named { name = noPos (name t), value = noPos (value t) }
instance NoPos t => NoPos [t] where noPos = fmap noPos
instance NoPos t => NoPos (Maybe t) where noPos = fmap noPos
instance NoPos (Program name) where
noPos (Program x) = Program (noPos x)
instance NoPos (Module name) where
noPos m = Module { mName = mName m
, mImports = noPos (mImports m)
, mDecls = noPos (mDecls m)
}
instance NoPos (TopDecl name) where
noPos decl =
case decl of
Decl x -> Decl (noPos x)
TDNewtype n -> TDNewtype(noPos n)
Include x -> Include (noPos x)
instance NoPos a => NoPos (TopLevel a) where
noPos tl = tl { tlValue = noPos (tlValue tl) }
instance NoPos (Decl name) where
noPos decl =
case decl of
DSignature x y -> DSignature (noPos x) (noPos y)
DPragma x y -> DPragma (noPos x) (noPos y)
DPatBind x y -> DPatBind (noPos x) (noPos y)
DFixity f ns -> DFixity f (noPos ns)
DBind x -> DBind (noPos x)
DType x -> DType (noPos x)
DLocated x _ -> noPos x
instance NoPos (Newtype name) where
noPos n = Newtype { nName = noPos (nName n)
, nParams = nParams n
, nBody = noPos (nBody n)
}
instance NoPos (Bind name) where
noPos x = Bind { bName = noPos (bName x)
, bParams = noPos (bParams x)
, bDef = noPos (bDef x)
, bSignature = noPos (bSignature x)
, bInfix = bInfix x
, bFixity = bFixity x
, bPragmas = noPos (bPragmas x)
, bMono = bMono x
, bDoc = bDoc x
}
instance NoPos Pragma where
noPos p@(PragmaNote {}) = p
noPos p@(PragmaProperty) = p
instance NoPos (TySyn name) where
noPos (TySyn x y z) = TySyn (noPos x) (noPos y) (noPos z)
instance NoPos (Expr name) where
noPos expr =
case expr of
EVar x -> EVar x
ELit x -> ELit x
ETuple x -> ETuple (noPos x)
ERecord x -> ERecord (noPos x)
ESel x y -> ESel (noPos x) y
EList x -> EList (noPos x)
EFromTo x y z -> EFromTo (noPos x) (noPos y) (noPos z)
EInfFrom x y -> EInfFrom (noPos x) (noPos y)
EComp x y -> EComp (noPos x) (noPos y)
EApp x y -> EApp (noPos x) (noPos y)
EAppT x y -> EAppT (noPos x) (noPos y)
EIf x y z -> EIf (noPos x) (noPos y) (noPos z)
EWhere x y -> EWhere (noPos x) (noPos y)
ETyped x y -> ETyped (noPos x) (noPos y)
ETypeVal x -> ETypeVal (noPos x)
EFun x y -> EFun (noPos x) (noPos y)
ELocated x _ -> noPos x
EParens e -> EParens (noPos e)
EInfix x y f z-> EInfix (noPos x) y f (noPos z)
instance NoPos (TypeInst name) where
noPos (PosInst ts) = PosInst (noPos ts)
noPos (NamedInst fs) = NamedInst (noPos fs)
instance NoPos (Match name) where
noPos (Match x y) = Match (noPos x) (noPos y)
noPos (MatchLet b) = MatchLet (noPos b)
instance NoPos (Pattern name) where
noPos pat =
case pat of
PVar x -> PVar (noPos x)
PWild -> PWild
PTuple x -> PTuple (noPos x)
PRecord x -> PRecord (noPos x)
PList x -> PList (noPos x)
PTyped x y -> PTyped (noPos x) (noPos y)
PSplit x y -> PSplit (noPos x) (noPos y)
PLocated x _ -> noPos x
instance NoPos (Schema name) where
noPos (Forall x y z _) = Forall (noPos x) (noPos y) (noPos z) Nothing
instance NoPos (TParam name) where
noPos (TParam x y _) = TParam x y Nothing
instance NoPos (Type name) where
noPos ty =
case ty of
TWild -> TWild
TApp x y -> TApp x (noPos y)
TUser x y -> TUser x (noPos y)
TRecord x -> TRecord (noPos x)
TTuple x -> TTuple (noPos x)
TFun x y -> TFun (noPos x) (noPos y)
TSeq x y -> TSeq (noPos x) (noPos y)
TBit -> TBit
TInf -> TInf
TNum n -> TNum n
TChar n -> TChar n
TLocated x _ -> noPos x
TParens x -> TParens (noPos x)
TInfix x y f z-> TInfix (noPos x) y f (noPos z)
instance NoPos (Prop name) where
noPos prop =
case prop of
CEqual x y -> CEqual (noPos x) (noPos y)
CGeq x y -> CGeq (noPos x) (noPos y)
CFin x -> CFin (noPos x)
CArith x -> CArith (noPos x)
CCmp x -> CCmp (noPos x)
CLocated c _ -> noPos c
CType t -> CType (noPos t)
cryptol-2.4.0/src/Cryptol/Parser/Lexer.x 0000644 0000000 0000000 00000017457 12737220176 016353 0 ustar 00 0000000 0000000 {
-- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- At present Alex generates code with too many warnings.
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -w #-}
module Cryptol.Parser.Lexer
( primLexer, lexer, Layout(..)
, Token(..), TokenT(..)
, TokenV(..), TokenKW(..), TokenErr(..), TokenSym(..), TokenW(..)
, Located(..)
, Config(..)
, defaultConfig
) where
import Cryptol.Parser.Position
import Cryptol.Parser.LexerUtils
import Cryptol.Parser.Unlit(unLit)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as Text
}
$uniupper = \x1
$unilower = \x2
$unidigit = \x3
$unisymbol = \x4
$unispace = \x5
$uniother = \x6
$unitick = \x7
@id_first = [a-zA-Z_] | $unilower | $uniupper
@id_next = [a-zA-Z0-9_'] | $unilower | $uniupper | $unidigit | $unitick
@id = @id_first @id_next*
@op = ([\!\@\#\$\%\^\&\*\~\>\<\?\+\=\|\/\\\-] | $unisymbol)+
@qual = (@id $white* :: $white*)+
@qual_id = @qual @id
@qual_op = @qual @op
@num2 = "0b" [0-1]+
@num8 = "0o" [0-7]+
@num10 = [0-9]+
@num16 = "0x" [0-9A-Fa-f]+
@strPart = [^\\\"]+
@chrPart = [^\\\']+
:-
<0,comment> {
\/\* { startComment False }
\/\*\*+ { startComment True }
\/\*+\/ { startEndComment }
}
{
\*+\/ { endComent }
[^\*\/]+ { addToComment }
\* { addToComment }
\/ { addToComment }
\n { addToComment }
}
{
@strPart { addToString }
\" { endString }
\\. { addToString }
\n { endString }
}
{
@chrPart { addToChar }
\' { endChar }
\\. { addToChar }
\n { endChar }
}
<0> {
$white+ { emit $ White Space }
"//" .* { emit $ White LineComment }
@qual_id { mkQualIdent }
@qual_op { mkQualOp }
-- Please update the docs, if you add new entries.
"else" { emit $ KW KW_else }
"extern" { emit $ KW KW_extern }
"if" { emit $ KW KW_if }
"private" { emit $ KW KW_private }
"include" { emit $ KW KW_include }
"module" { emit $ KW KW_module }
"newtype" { emit $ KW KW_newtype }
"pragma" { emit $ KW KW_pragma }
"property" { emit $ KW KW_property }
"then" { emit $ KW KW_then }
"type" { emit $ KW KW_type }
"where" { emit $ KW KW_where }
"let" { emit $ KW KW_let }
"x" { emit $ KW KW_x }
"import" { emit $ KW KW_import }
"as" { emit $ KW KW_as }
"hiding" { emit $ KW KW_hiding }
"newtype" { emit $ KW KW_newtype }
"infixl" { emit $ KW KW_infixl }
"infixr" { emit $ KW KW_infixr }
"infix" { emit $ KW KW_infix }
"primitive" { emit $ KW KW_primitive }
@num2 { emitS (numToken 2 . Text.drop 2) }
@num8 { emitS (numToken 8 . Text.drop 2) }
@num10 { emitS (numToken 10 . Text.drop 0) }
@num16 { emitS (numToken 16 . Text.drop 2) }
"_" { emit $ Sym Underscore }
@id { mkIdent }
"\" { emit $ Sym Lambda }
"->" { emit $ Sym ArrR }
"<-" { emit $ Sym ArrL }
"=>" { emit $ Sym FatArrR }
"=" { emit $ Sym EqDef }
"," { emit $ Sym Comma }
";" { emit $ Sym Semi }
"." { emit $ Sym Dot }
":" { emit $ Sym Colon }
"`" { emit $ Sym BackTick }
".." { emit $ Sym DotDot }
"..." { emit $ Sym DotDotDot }
"|" { emit $ Sym Bar }
"(" { emit $ Sym ParenL }
")" { emit $ Sym ParenR }
"[" { emit $ Sym BracketL }
"]" { emit $ Sym BracketR }
"{" { emit $ Sym CurlyL }
"}" { emit $ Sym CurlyR }
"<|" { emit $ Sym TriL }
"|>" { emit $ Sym TriR }
\" { startString }
\' { startChar }
-- special cases for types and kinds
"+" { emit (Op Plus ) }
"-" { emit (Op Minus) }
"*" { emit (Op Mul ) }
"^^" { emit (Op Exp ) }
-- hash is used as a kind, and as a pattern
"#" { emit (Op Hash ) }
-- ~ is used for unary complement
"~" { emit (Op Complement) }
-- all other operators
@op { emitS (Op . Other []) }
}
{
-- This code is here because it depends on `comment`, which is defined
-- in this file.
stateToInt :: LexS -> Int
stateToInt Normal = 0
stateToInt (InComment {}) = comment
stateToInt (InString {}) = string
stateToInt (InChar {}) = char
-- | Returns the tokens in the last position of the input that we processed.
-- White space is removed, and layout processing is done as requested.
-- This stream is fed to the parser.
lexer :: Config -> Text -> ([Located Token], Position)
lexer cfg cs = ( case cfgLayout cfg of
Layout -> layout cfg lexemes
NoLayout -> lexemes
, finalPos
)
where (lex0, finalPos) = primLexer cfg cs
lexemes = dropWhite lex0
-- | Returns the tokens and the last position of the input that we processed.
-- The tokens include whte space tokens.
primLexer :: Config -> Text -> ([Located Token], Position)
primLexer cfg cs = run inp Normal
where
inp = Inp { alexPos = start
, alexInputPrevChar = '\n'
, input = unLit (cfgPreProc cfg) cs }
singleR p = Range p p (cfgSource cfg)
eofR p = Range p' p' (cfgSource cfg)
where
p' = Position { line = line p + 1, col = 0 }
run i s =
case alexScan i (stateToInt s) of
AlexEOF ->
case s of
Normal -> ([ Located (eofR $ alexPos i) (Token EOF "end of file") ]
, alexPos i
)
InComment _ p _ _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedComment) "unterminated comment"
]
, alexPos i)
InString p _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedString) "unterminated string"
]
, alexPos i)
InChar p _ ->
( [ Located (singleR p)
$ Token (Err UnterminatedChar) "unterminated character"
]
, alexPos i)
AlexError i' ->
let bad = Text.take 1 (input i)
in
( [ Located (Range (alexPos i) (alexPos i') (cfgSource cfg))
$ Token (Err LexicalError) bad ]
, alexPos i')
AlexSkip i' _ -> run i' s
AlexToken i' l act ->
let txt = Text.take (fromIntegral l) (input i)
(mtok,s') = act cfg (alexPos i) txt s
(rest,pos) = run i' $! s'
in case mtok of
Nothing -> (rest, pos)
Just t -> (t : rest, pos)
-- vim: ft=haskell
}
cryptol-2.4.0/src/Cryptol/Parser/LexerUtils.hs 0000644 0000000 0000000 00000041504 12737220176 017525 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.Parser.LexerUtils where
import Cryptol.Parser.Position
import Cryptol.Parser.Unlit(PreProc(None))
import Cryptol.Utils.PP
import Cryptol.Utils.Panic
import Data.Char(toLower,generalCategory,isAscii,ord,isSpace)
import qualified Data.Char as Char
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Data.Word(Word8)
import GHC.Generics (Generic)
import Control.DeepSeq
data Config = Config
{ cfgSource :: !FilePath -- ^ File that we are working on
, cfgLayout :: !Layout -- ^ Settings for layout processing
, cfgPreProc :: PreProc -- ^ Preprocessor settings
, cfgAutoInclude :: [FilePath] -- ^ Implicit includes
, cfgModuleScope :: Bool -- ^ When we do layout processing
-- should we add a vCurly (i.e., are
-- we parsing a list of things).
}
defaultConfig :: Config
defaultConfig = Config
{ cfgSource = ""
, cfgLayout = Layout
, cfgPreProc = None
, cfgAutoInclude = []
, cfgModuleScope = True
}
type Action = Config -> Position -> Text -> LexS
-> (Maybe (Located Token), LexS)
data LexS = Normal
| InComment Bool Position ![Position] [Text]
| InString Position Text
| InChar Position Text
startComment :: Bool -> Action
startComment isDoc _ p txt s = (Nothing, InComment d p stack chunks)
where (d,stack,chunks) = case s of
Normal -> (isDoc, [], [txt])
InComment doc q qs cs -> (doc, q : qs, txt : cs)
_ -> panic "[Lexer] startComment" ["in a string"]
endComent :: Action
endComent cfg p txt s =
case s of
InComment d f [] cs -> (Just (mkToken d f cs), Normal)
InComment d _ (q:qs) cs -> (Nothing, InComment d q qs (txt : cs))
_ -> panic "[Lexer] endComment" ["outside comment"]
where
mkToken isDoc f cs =
let r = Range { from = f, to = moves p txt, source = cfgSource cfg }
str = T.concat $ reverse $ txt : cs
tok = if isDoc then DocStr else BlockComment
in Located { srcRange = r, thing = Token (White tok) str }
addToComment :: Action
addToComment _ _ txt s = (Nothing, InComment doc p stack (txt : chunks))
where
(doc, p, stack, chunks) =
case s of
InComment d q qs cs -> (d,q,qs,cs)
_ -> panic "[Lexer] addToComment" ["outside comment"]
startEndComment :: Action
startEndComment cfg p txt s =
case s of
Normal -> (Just tok, Normal)
where tok = Located
{ srcRange = Range { from = p
, to = moves p txt
, source = cfgSource cfg
}
, thing = Token (White BlockComment) txt
}
InComment d p1 ps cs -> (Nothing, InComment d p1 ps (txt : cs))
_ -> panic "[Lexer] startEndComment" ["in string or char?"]
startString :: Action
startString _ p txt _ = (Nothing,InString p txt)
endString :: Action
endString cfg pe txt s = case s of
InString ps str -> (Just (mkToken ps str), Normal)
_ -> panic "[Lexer] endString" ["outside string"]
where
parseStr s1 = case reads s1 of
[(cs, "")] -> StrLit cs
_ -> Err InvalidString
mkToken ps str = Located { srcRange = Range
{ from = ps
, to = moves pe txt
, source = cfgSource cfg
}
, thing = Token
{ tokenType = parseStr (T.unpack tokStr)
, tokenText = tokStr
}
}
where
tokStr = str `T.append` txt
addToString :: Action
addToString _ _ txt s = case s of
InString p str -> (Nothing,InString p (str `T.append` txt))
_ -> panic "[Lexer] addToString" ["outside string"]
startChar :: Action
startChar _ p txt _ = (Nothing,InChar p txt)
endChar :: Action
endChar cfg pe txt s =
case s of
InChar ps str -> (Just (mkToken ps str), Normal)
_ -> panic "[Lexer] endString" ["outside character"]
where
parseChar s1 = case reads s1 of
[(cs, "")] -> ChrLit cs
_ -> Err InvalidChar
mkToken ps str = Located { srcRange = Range
{ from = ps
, to = moves pe txt
, source = cfgSource cfg
}
, thing = Token
{ tokenType = parseChar (T.unpack tokStr)
, tokenText = tokStr
}
}
where
tokStr = str `T.append` txt
addToChar :: Action
addToChar _ _ txt s = case s of
InChar p str -> (Nothing,InChar p (str `T.append` txt))
_ -> panic "[Lexer] addToChar" ["outside character"]
mkIdent :: Action
mkIdent cfg p s z = (Just Located { srcRange = r, thing = Token t s }, z)
where
r = Range { from = p, to = moves p s, source = cfgSource cfg }
t = Ident [] s
mkQualIdent :: Action
mkQualIdent cfg p s z = (Just Located { srcRange = r, thing = Token t s}, z)
where
r = Range { from = p, to = moves p s, source = cfgSource cfg }
t = Ident ns i
(ns,i) = splitQual s
mkQualOp :: Action
mkQualOp cfg p s z = (Just Located { srcRange = r, thing = Token t s}, z)
where
r = Range { from = p, to = moves p s, source = cfgSource cfg }
t = Op (Other ns i)
(ns,i) = splitQual s
emit :: TokenT -> Action
emit t cfg p s z = (Just Located { srcRange = r, thing = Token t s }, z)
where r = Range { from = p, to = moves p s, source = cfgSource cfg }
emitS :: (Text -> TokenT) -> Action
emitS t cfg p s z = emit (t s) cfg p s z
-- | Split out the prefix and name part of an identifier/operator.
splitQual :: T.Text -> ([T.Text], T.Text)
splitQual t =
case splitNS (T.filter (not . isSpace) t) of
[] -> panic "[Lexer] mkQualIdent" ["invalid qualified name", show t]
[i] -> ([], i)
xs -> (init xs, last xs)
where
-- split on the namespace separator, `::`
splitNS s =
case T.breakOn "::" s of
(l,r) | T.null r -> [l]
| otherwise -> l : splitNS (T.drop 2 r)
--------------------------------------------------------------------------------
numToken :: Integer -> Text -> TokenT
numToken rad ds = Num (toVal ds) (fromInteger rad) (fromIntegral (T.length ds))
where
toVal = T.foldl' (\x c -> rad * x + toDig c) 0
toDig = if rad == 16 then fromHexDigit else fromDecDigit
fromDecDigit :: Char -> Integer
fromDecDigit x = read [x]
fromHexDigit :: Char -> Integer
fromHexDigit x'
| 'a' <= x && x <= 'f' = fromIntegral (10 + fromEnum x - fromEnum 'a')
| otherwise = fromDecDigit x
where x = toLower x'
-------------------------------------------------------------------------------
data AlexInput = Inp { alexPos :: !Position
, alexInputPrevChar :: !Char
, input :: !Text
} deriving Show
alexGetByte :: AlexInput -> Maybe (Word8, AlexInput)
alexGetByte i =
do (c,rest) <- T.uncons (input i)
let i' = i { alexPos = move (alexPos i) c, input = rest }
b = byteForChar c
return (b,i')
data Layout = Layout | NoLayout
--------------------------------------------------------------------------------
-- | Drop white-space tokens from the input.
dropWhite :: [Located Token] -> [Located Token]
dropWhite = filter (notWhite . tokenType . thing)
where notWhite (White w) = w == DocStr
notWhite _ = True
data Block = Virtual Int -- ^ Virtual layout block
| Explicit TokenT -- ^ An explicit layout block, expecting this ending
-- token.
deriving (Show)
isExplicit :: Block -> Bool
isExplicit Explicit{} = True
isExplicit Virtual{} = False
startsLayout :: TokenT -> Bool
startsLayout (KW KW_where) = True
startsLayout (KW KW_private) = True
startsLayout _ = False
-- Add separators computed from layout
layout :: Config -> [Located Token] -> [Located Token]
layout cfg ts0 = loop False implicitScope [] ts0
where
(_pos0,implicitScope) = case ts0 of
t : _ -> (from (srcRange t), cfgModuleScope cfg && tokenType (thing t) /= KW KW_module)
_ -> (start,False)
loop :: Bool -> Bool -> [Block] -> [Located Token] -> [Located Token]
loop afterDoc startBlock stack (t : ts)
| startsLayout ty = toks ++ loop False True stack' ts
| Sym ParenL <- ty = toks ++ loop False False (Explicit (Sym ParenR) : stack') ts
| Sym CurlyL <- ty = toks ++ loop False False (Explicit (Sym CurlyR) : stack') ts
| Sym BracketL <- ty = toks ++ loop False False (Explicit (Sym BracketR) : stack') ts
| EOF <- ty = toks
| White DocStr <- ty = toks ++ loop True False stack' ts
| otherwise = toks ++ loop False False stack' ts
where
ty = tokenType (thing t)
pos = srcRange t
(toks,offStack)
| afterDoc = ([t], stack)
| otherwise = offsides startToks t stack
-- add any block start tokens, and push a level on the stack
(startToks,stack')
| startBlock && ty == EOF = ( [ virt cfg (to pos) VCurlyR
, virt cfg (to pos) VCurlyL ]
, offStack )
| startBlock = ( [ virt cfg (to pos) VCurlyL ], Virtual (col (from pos)) : offStack )
| otherwise = ( [], offStack )
loop _ _ _ [] = panic "[Lexer] layout" ["Missing EOF token"]
offsides :: [Located Token] -> Located Token -> [Block] -> ([Located Token], [Block])
offsides startToks t = go startToks
where
go virts stack = case stack of
-- delimit or close a layout block
Virtual c : rest
-- commas only close to an explicit marker, so if there is none, the
-- comma doesn't close anything
| Sym Comma == ty ->
if any isExplicit rest
then go (virt cfg (to pos) VCurlyR : virts) rest
else done virts stack
| closingToken -> go (virt cfg (to pos) VCurlyR : virts) rest
| col (from pos) == c -> done (virt cfg (to pos) VSemi : virts) stack
| col (from pos) < c -> go (virt cfg (to pos) VCurlyR : virts) rest
-- close an explicit block
Explicit close : rest | close == ty -> done virts rest
| Sym Comma == ty -> done virts stack
_ -> done virts stack
ty = tokenType (thing t)
pos = srcRange t
done ts s = (reverse (t:ts), s)
closingToken = ty `elem` [ Sym ParenR, Sym BracketR, Sym CurlyR ]
virt :: Config -> Position -> TokenV -> Located Token
virt cfg pos x = Located { srcRange = Range
{ from = pos
, to = pos
, source = cfgSource cfg
}
, thing = t }
where t = Token (Virt x) $ case x of
VCurlyL -> "beginning of layout block"
VCurlyR -> "end of layout block"
VSemi -> "layout block separator"
--------------------------------------------------------------------------------
data Token = Token { tokenType :: TokenT, tokenText :: Text }
deriving (Show, Generic, NFData)
-- | Virtual tokens, inserted by layout processing.
data TokenV = VCurlyL| VCurlyR | VSemi
deriving (Eq, Show, Generic, NFData)
data TokenW = BlockComment | LineComment | Space | DocStr
deriving (Eq, Show, Generic, NFData)
data TokenKW = KW_Arith
| KW_Bit
| KW_Cmp
| KW_else
| KW_Eq
| KW_extern
| KW_fin
| KW_if
| KW_private
| KW_include
| KW_inf
| KW_lg2
| KW_lengthFromThen
| KW_lengthFromThenTo
| KW_max
| KW_min
| KW_module
| KW_newtype
| KW_pragma
| KW_property
| KW_then
| KW_type
| KW_where
| KW_let
| KW_x
| KW_import
| KW_as
| KW_hiding
| KW_infixl
| KW_infixr
| KW_infix
| KW_primitive
deriving (Eq, Show, Generic, NFData)
-- | The named operators are a special case for parsing types, and 'Other' is
-- used for all other cases that lexed as an operator.
data TokenOp = Plus | Minus | Mul | Div | Exp | Mod
| Equal | LEQ | GEQ
| Complement | Hash
| Other [T.Text] T.Text
deriving (Eq, Show, Generic, NFData)
data TokenSym = Bar
| ArrL | ArrR | FatArrR
| Lambda
| EqDef
| Comma
| Semi
| Dot
| DotDot
| DotDotDot
| Colon
| BackTick
| ParenL | ParenR
| BracketL | BracketR
| CurlyL | CurlyR
| TriL | TriR
| Underscore
deriving (Eq, Show, Generic, NFData)
data TokenErr = UnterminatedComment
| UnterminatedString
| UnterminatedChar
| InvalidString
| InvalidChar
| LexicalError
deriving (Eq, Show, Generic, NFData)
data TokenT = Num Integer Int Int -- ^ value, base, number of digits
| ChrLit Char -- ^ character literal
| Ident [T.Text] T.Text -- ^ (qualified) identifier
| StrLit String -- ^ string literal
| KW TokenKW -- ^ keyword
| Op TokenOp -- ^ operator
| Sym TokenSym -- ^ symbol
| Virt TokenV -- ^ virtual token (for layout)
| White TokenW -- ^ white space token
| Err TokenErr -- ^ error token
| EOF
deriving (Eq, Show, Generic, NFData)
instance PP Token where
ppPrec _ (Token _ s) = text (T.unpack s)
-- | Collapse characters into a single Word8, identifying ASCII, and classes of
-- unicode. This came from:
--
-- https://github.com/glguy/config-value/blob/master/src/Config/LexerUtils.hs
--
-- Which adapted:
--
-- https://github.com/ghc/ghc/blob/master/compiler/parser/Lexer.x
byteForChar :: Char -> Word8
byteForChar c
| c <= '\6' = non_graphic
| isAscii c = fromIntegral (ord c)
| otherwise = case generalCategory c of
Char.LowercaseLetter -> lower
Char.OtherLetter -> lower
Char.UppercaseLetter -> upper
Char.TitlecaseLetter -> upper
Char.DecimalNumber -> digit
Char.OtherNumber -> digit
Char.ConnectorPunctuation -> symbol
Char.DashPunctuation -> symbol
Char.OtherPunctuation -> symbol
Char.MathSymbol -> symbol
Char.CurrencySymbol -> symbol
Char.ModifierSymbol -> symbol
Char.OtherSymbol -> symbol
Char.Space -> sp
Char.ModifierLetter -> other
Char.NonSpacingMark -> other
Char.SpacingCombiningMark -> other
Char.EnclosingMark -> other
Char.LetterNumber -> other
Char.OpenPunctuation -> other
Char.ClosePunctuation -> other
Char.InitialQuote -> other
Char.FinalQuote -> tick
_ -> non_graphic
where
non_graphic = 0
upper = 1
lower = 2
digit = 3
symbol = 4
sp = 5
other = 6
tick = 7
cryptol-2.4.0/src/Cryptol/Parser/Name.hs 0000644 0000000 0000000 00000004173 12737220176 016306 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.Parser.Name where
import Cryptol.Utils.Ident
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import Control.DeepSeq
import qualified Data.Text as T
import GHC.Generics (Generic)
-- Names -----------------------------------------------------------------------
-- | Names that originate in the parser.
data PName = UnQual !Ident
-- ^ Unqualified names like @x@, @Foo@, or @+@.
| Qual !ModName !Ident
-- ^ Qualified names like @Foo::bar@ or @module::!@.
| NewName !Pass !Int
-- ^ Fresh names generated by a pass.
deriving (Eq,Ord,Show,Generic)
-- | Passes that can generate fresh names.
data Pass = NoPat
| MonoValues
deriving (Eq,Ord,Show,Generic)
instance NFData PName
instance NFData Pass
mkUnqual :: Ident -> PName
mkUnqual = UnQual
mkQual :: ModName -> Ident -> PName
mkQual = Qual
getModName :: PName -> Maybe ModName
getModName (Qual ns _) = Just ns
getModName _ = Nothing
getIdent :: PName -> Ident
getIdent (UnQual n) = n
getIdent (Qual _ n) = n
getIdent (NewName p i) = Ident False (T.pack ("__" ++ pass ++ show i))
where
pass = case p of
NoPat -> "p"
MonoValues -> "mv"
instance PP PName where
ppPrec _ = ppPrefixName
instance PPName PName where
ppNameFixity n
| isInfixIdent i = Just (NonAssoc, 0) -- FIXME?
| otherwise = Nothing
where
i = getIdent n
ppPrefixName n = optParens (isInfixIdent i) (pfx <> pp i)
where
i = getIdent n
pfx = case getModName n of
Just ns -> pp ns <> text "::"
Nothing -> empty
ppInfixName n
| isInfixIdent i = pfx <> pp i
| otherwise = panic "AST" [ "non-symbol infix name:" ++ show n ]
where
i = getIdent n
pfx = case getModName n of
Just ns -> pp ns <> text "::"
Nothing -> empty
cryptol-2.4.0/src/Cryptol/Parser/Names.hs 0000644 0000000 0000000 00000024370 12737220176 016472 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- This module defines the scoping rules for value- and type-level
-- names in Cryptol.
module Cryptol.Parser.Names where
import Cryptol.Parser.AST
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Foldable (fold)
modExports :: Ord name => Module name -> ExportSpec name
modExports m = fold (concat [ exportedNames d | d <- mDecls m ])
where
names by td = [ td { tlValue = thing n } | n <- fst (by (tlValue td)) ]
exportedNames (Decl td) = map exportBind (names namesD td)
++ map exportType (names tnamesD td)
exportedNames (TDNewtype nt) = map exportType (names tnamesNT nt)
exportedNames (Include {}) = []
-- | The names defined by a newtype.
tnamesNT :: Newtype name -> ([Located name], ())
tnamesNT x = ([ nName x ], ())
-- | The names defined and used by a group of mutually recursive declarations.
namesDs :: Ord name => [Decl name] -> ([Located name], Set name)
namesDs ds = (defs, boundNames defs (Set.unions frees))
where
defs = concat defss
(defss,frees) = unzip (map namesD ds)
-- | The names defined and used by a single declarations.
namesD :: Ord name => Decl name -> ([Located name], Set name)
namesD decl =
case decl of
DBind b -> namesB b
DPatBind p e -> (namesP p, namesE e)
DSignature {} -> ([],Set.empty)
DFixity{} -> ([],Set.empty)
DPragma {} -> ([],Set.empty)
DType {} -> ([],Set.empty)
DLocated d _ -> namesD d
-- | The names defined and used by a single declarations in such a way
-- that they cannot be duplicated in a file. For example, it is fine
-- to use @x@ on the RHS of two bindings, but not on the LHS of two
-- type signatures.
allNamesD :: Ord name => Decl name -> [Located name]
allNamesD decl =
case decl of
DBind b -> fst (namesB b)
DPatBind p _ -> namesP p
DSignature ns _ -> ns
DFixity _ ns -> ns
DPragma ns _ -> ns
DType ts -> [tsName ts]
DLocated d _ -> allNamesD d
tsName :: TySyn name -> Located name
tsName (TySyn lqn _ _) = lqn
-- | The names defined and used by a single binding.
namesB :: Ord name => Bind name -> ([Located name], Set name)
namesB b = ([bName b], boundNames (namesPs (bParams b)) (namesDef (thing (bDef b))))
namesDef :: Ord name => BindDef name -> Set name
namesDef DPrim = Set.empty
namesDef (DExpr e) = namesE e
-- | The names used by an expression.
namesE :: Ord name => Expr name -> Set name
namesE expr =
case expr of
EVar x -> Set.singleton x
ELit _ -> Set.empty
ETuple es -> Set.unions (map namesE es)
ERecord fs -> Set.unions (map (namesE . value) fs)
ESel e _ -> namesE e
EList es -> Set.unions (map namesE es)
EFromTo _ _ _ -> Set.empty
EInfFrom e e' -> Set.union (namesE e) (maybe Set.empty namesE e')
EComp e arms -> let (dss,uss) = unzip (map namesArm arms)
in Set.union (boundNames (concat dss) (namesE e))
(Set.unions uss)
EApp e1 e2 -> Set.union (namesE e1) (namesE e2)
EAppT e _ -> namesE e
EIf e1 e2 e3 -> Set.union (namesE e1) (Set.union (namesE e2) (namesE e3))
EWhere e ds -> let (bs,xs) = namesDs ds
in Set.union (boundNames bs (namesE e)) xs
ETyped e _ -> namesE e
ETypeVal _ -> Set.empty
EFun ps e -> boundNames (namesPs ps) (namesE e)
ELocated e _ -> namesE e
EParens e -> namesE e
EInfix a o _ b-> Set.insert (thing o) (Set.union (namesE a) (namesE b))
-- | The names defined by a group of patterns.
namesPs :: [Pattern name] -> [Located name]
namesPs = concatMap namesP
-- | The names defined by a pattern. These will always be unqualified names.
namesP :: Pattern name -> [Located name]
namesP pat =
case pat of
PVar x -> [x]
PWild -> []
PTuple ps -> namesPs ps
PRecord fs -> namesPs (map value fs)
PList ps -> namesPs ps
PTyped p _ -> namesP p
PSplit p1 p2 -> namesPs [p1,p2]
PLocated p _ -> namesP p
-- | The names defined and used by a match.
namesM :: Ord name => Match name -> ([Located name], Set name)
namesM (Match p e) = (namesP p, namesE e)
namesM (MatchLet b) = namesB b
-- | The names defined and used by an arm of alist comprehension.
namesArm :: Ord name => [Match name] -> ([Located name], Set name)
namesArm = foldr combine ([],Set.empty) . map namesM
where combine (ds1,fs1) (ds2,fs2) =
( filter ((`notElem` map thing ds2) . thing) ds1 ++ ds2
, Set.union fs1 (boundNames ds1 fs2)
)
-- | Remove some defined variables from a set of free variables.
boundNames :: Ord name => [Located name] -> Set name -> Set name
boundNames bs xs = Set.difference xs (Set.fromList (map thing bs))
-- | Given the set of type variables that are in scope,
-- compute the type synonyms used by a type.
namesT :: Ord name => Set name -> Type name -> Set name
namesT vs = go
where
go ty =
case ty of
TWild -> Set.empty
TFun t1 t2 -> Set.union (go t1) (go t2)
TSeq t1 t2 -> Set.union (go t1) (go t2)
TBit -> Set.empty
TNum _ -> Set.empty
TChar _ -> Set.empty
TInf -> Set.empty
TApp _ ts -> Set.unions (map go ts)
TTuple ts -> Set.unions (map go ts)
TRecord fs -> Set.unions (map (go . value) fs)
TLocated t _ -> go t
TUser x [] | x `Set.member` vs
-> Set.empty
TUser x ts -> Set.insert x (Set.unions (map go ts))
TParens t -> namesT vs t
TInfix a _ _ b-> Set.union (namesT vs a) (namesT vs b)
-- | The type names defined and used by a group of mutually recursive declarations.
tnamesDs :: Ord name => [Decl name] -> ([Located name], Set name)
tnamesDs ds = (defs, boundNames defs (Set.unions frees))
where
defs = concat defss
(defss,frees) = unzip (map tnamesD ds)
-- | The type names defined and used by a single declaration.
tnamesD :: Ord name => Decl name -> ([Located name], Set name)
tnamesD decl =
case decl of
DSignature _ s -> ([], tnamesS s)
DFixity {} -> ([], Set.empty)
DPragma {} -> ([], Set.empty)
DBind b -> ([], tnamesB b)
DPatBind _ e -> ([], tnamesE e)
DLocated d _ -> tnamesD d
DType (TySyn n ps t) -> ([n], Set.difference (tnamesT t) (Set.fromList (map tpName ps)))
-- | The type names used by a single binding.
tnamesB :: Ord name => Bind name -> Set name
tnamesB b = Set.unions [setS, setP, setE]
where
setS = maybe Set.empty tnamesS (bSignature b)
setP = Set.unions (map tnamesP (bParams b))
setE = tnamesDef (thing (bDef b))
tnamesDef :: Ord name => BindDef name -> Set name
tnamesDef DPrim = Set.empty
tnamesDef (DExpr e) = tnamesE e
-- | The type names used by an expression.
tnamesE :: Ord name => Expr name -> Set name
tnamesE expr =
case expr of
EVar _ -> Set.empty
ELit _ -> Set.empty
ETuple es -> Set.unions (map tnamesE es)
ERecord fs -> Set.unions (map (tnamesE . value) fs)
ESel e _ -> tnamesE e
EList es -> Set.unions (map tnamesE es)
EFromTo a b c -> Set.union (tnamesT a)
(Set.union (maybe Set.empty tnamesT b) (maybe Set.empty tnamesT c))
EInfFrom e e' -> Set.union (tnamesE e) (maybe Set.empty tnamesE e')
EComp e mss -> Set.union (tnamesE e) (Set.unions (map tnamesM (concat mss)))
EApp e1 e2 -> Set.union (tnamesE e1) (tnamesE e2)
EAppT e fs -> Set.union (tnamesE e) (Set.unions (map tnamesTI fs))
EIf e1 e2 e3 -> Set.union (tnamesE e1) (Set.union (tnamesE e2) (tnamesE e3))
EWhere e ds -> let (bs,xs) = tnamesDs ds
in Set.union (boundNames bs (tnamesE e)) xs
ETyped e t -> Set.union (tnamesE e) (tnamesT t)
ETypeVal t -> tnamesT t
EFun ps e -> Set.union (Set.unions (map tnamesP ps)) (tnamesE e)
ELocated e _ -> tnamesE e
EParens e -> tnamesE e
EInfix a _ _ b-> Set.union (tnamesE a) (tnamesE b)
tnamesTI :: Ord name => TypeInst name -> Set name
tnamesTI (NamedInst f) = tnamesT (value f)
tnamesTI (PosInst t) = tnamesT t
-- | The type names used by a pattern.
tnamesP :: Ord name => Pattern name -> Set name
tnamesP pat =
case pat of
PVar _ -> Set.empty
PWild -> Set.empty
PTuple ps -> Set.unions (map tnamesP ps)
PRecord fs -> Set.unions (map (tnamesP . value) fs)
PList ps -> Set.unions (map tnamesP ps)
PTyped p t -> Set.union (tnamesP p) (tnamesT t)
PSplit p1 p2 -> Set.union (tnamesP p1) (tnamesP p2)
PLocated p _ -> tnamesP p
-- | The type names used by a match.
tnamesM :: Ord name => Match name -> Set name
tnamesM (Match p e) = Set.union (tnamesP p) (tnamesE e)
tnamesM (MatchLet b) = tnamesB b
-- | The type names used by a type schema.
tnamesS :: Ord name => Schema name -> Set name
tnamesS (Forall params props ty _) =
Set.difference (Set.union (Set.unions (map tnamesC props)) (tnamesT ty))
(Set.fromList (map tpName params))
-- | The type names used by a prop.
tnamesC :: Ord name => Prop name -> Set name
tnamesC prop =
case prop of
CFin t -> tnamesT t
CEqual t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
CGeq t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
CArith t -> tnamesT t
CCmp t -> tnamesT t
CLocated p _ -> tnamesC p
CType t -> tnamesT t
-- | Compute the type synonyms/type variables used by a type.
tnamesT :: Ord name => Type name -> Set name
tnamesT ty =
case ty of
TWild -> Set.empty
TFun t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
TSeq t1 t2 -> Set.union (tnamesT t1) (tnamesT t2)
TBit -> Set.empty
TNum _ -> Set.empty
TChar __ -> Set.empty
TInf -> Set.empty
TApp _ ts -> Set.unions (map tnamesT ts)
TTuple ts -> Set.unions (map tnamesT ts)
TRecord fs -> Set.unions (map (tnamesT . value) fs)
TLocated t _ -> tnamesT t
TUser x ts -> Set.insert x (Set.unions (map tnamesT ts))
TParens t -> tnamesT t
TInfix a _ _ c-> Set.union (tnamesT a) (tnamesT c)
cryptol-2.4.0/src/Cryptol/Parser/NoInclude.hs 0000644 0000000 0000000 00000013404 12737220176 017303 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.Parser.NoInclude
( removeIncludesModule
, IncludeError(..), ppIncludeError
) where
import qualified Control.Applicative as A
import Control.DeepSeq
import qualified Control.Exception as X
import Data.Either (partitionEithers)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy.IO as T
import GHC.Generics (Generic)
import MonadLib
import System.Directory (makeAbsolute)
import System.FilePath (takeDirectory,(>),isAbsolute)
import Cryptol.Parser (parseProgramWith)
import Cryptol.Parser.AST
import Cryptol.Parser.LexerUtils (Config(..),defaultConfig)
import Cryptol.Parser.ParserUtils
import Cryptol.Parser.Unlit (guessPreProc)
import Cryptol.Utils.PP
removeIncludesModule :: FilePath -> Module PName -> IO (Either [IncludeError] (Module PName))
removeIncludesModule modPath m = runNoIncM modPath (noIncludeModule m)
data IncludeError
= IncludeFailed (Located FilePath)
| IncludeParseError ParseError
| IncludeCycle [Located FilePath]
deriving (Show, Generic, NFData)
ppIncludeError :: IncludeError -> Doc
ppIncludeError ie = case ie of
IncludeFailed lp -> (char '`' <> text (thing lp) <> char '`')
<+> text "included at"
<+> pp (srcRange lp)
<+> text "was not found"
IncludeParseError pe -> ppError pe
IncludeCycle is -> text "includes form a cycle:"
$$ nest 2 (vcat (map (pp . srcRange) is))
newtype NoIncM a = M
{ unM :: ReaderT Env (ExceptionT [IncludeError] IO) a }
data Env = Env { envSeen :: [Located FilePath]
-- ^ Files that have been loaded
, envIncPath :: FilePath
-- ^ The path that includes are relative to
}
runNoIncM :: FilePath -> NoIncM a -> IO (Either [IncludeError] a)
runNoIncM sourcePath m =
do incPath <- getIncPath sourcePath
runM (unM m) Env { envSeen = [], envIncPath = incPath }
tryNoIncM :: NoIncM a -> NoIncM (Either [IncludeError] a)
tryNoIncM m = M (try (unM m))
-- | Get the absolute directory name of a file that contains cryptol source.
getIncPath :: FilePath -> IO FilePath
getIncPath file = makeAbsolute (takeDirectory file)
-- | Run a 'NoIncM' action with a different include path. The argument is
-- expected to be the path of a file that contains cryptol source, and will be
-- adjusted with getIncPath.
withIncPath :: FilePath -> NoIncM a -> NoIncM a
withIncPath path (M body) = M $
do incPath <- inBase (getIncPath path)
env <- ask
local env { envIncPath = incPath } body
-- | Adjust an included file with the current include path.
fromIncPath :: FilePath -> NoIncM FilePath
fromIncPath path
| isAbsolute path = return path
| otherwise = M $
do Env { .. } <- ask
return (envIncPath > path)
instance Functor NoIncM where
fmap = liftM
instance A.Applicative NoIncM where
pure = return
(<*>) = ap
instance Monad NoIncM where
return x = M (return x)
m >>= f = M (unM m >>= unM . f)
fail x = M (fail x)
-- | Raise an 'IncludeFailed' error.
includeFailed :: Located FilePath -> NoIncM a
includeFailed path = M (raise [IncludeFailed path])
-- | Push a path on the stack of included files, and run an action. If the path
-- is already on the stack, an include cycle has happened, and an error is
-- raised.
pushPath :: Located FilePath -> NoIncM a -> NoIncM a
pushPath path m = M $ do
Env { .. } <- ask
let alreadyIncluded l = thing path == thing l
when (any alreadyIncluded envSeen) (raise [IncludeCycle envSeen])
local Env { envSeen = path:envSeen, .. } (unM m)
-- | Lift an IO operation, with a way to handle the exception that it might
-- throw.
failsWith :: X.Exception e => IO a -> (e -> NoIncM a) -> NoIncM a
failsWith m k = M $ do
e <- inBase (X.try m)
case e of
Right a -> return a
Left exn -> unM (k exn)
-- | Like 'mapM', but tries to collect as many errors as possible before
-- failing.
collectErrors :: (a -> NoIncM b) -> [a] -> NoIncM [b]
collectErrors f ts = do
es <- mapM (tryNoIncM . f) ts
let (ls,rs) = partitionEithers es
errs = concat ls
unless (null errs) (M (raise errs))
return rs
-- | Remove includes from a module.
noIncludeModule :: Module PName -> NoIncM (Module PName)
noIncludeModule m = update `fmap` collectErrors noIncTopDecl (mDecls m)
where
update tds = m { mDecls = concat tds }
-- | Remove includes from a program.
noIncludeProgram :: Program PName -> NoIncM (Program PName)
noIncludeProgram (Program tds) =
(Program . concat) `fmap` collectErrors noIncTopDecl tds
-- | Substitute top-level includes with the declarations from the files they
-- reference.
noIncTopDecl :: TopDecl PName -> NoIncM [TopDecl PName]
noIncTopDecl td = case td of
Decl _ -> return [td]
TDNewtype _-> return [td]
Include lf -> resolveInclude lf
-- | Resolve the file referenced by a include into a list of top-level
-- declarations.
resolveInclude :: Located FilePath -> NoIncM [TopDecl PName]
resolveInclude lf = pushPath lf $ do
source <- readInclude lf
case parseProgramWith (defaultConfig { cfgSource = thing lf, cfgPreProc = guessPreProc (thing lf) }) source of
Right prog -> do
Program ds <- withIncPath (thing lf) (noIncludeProgram prog)
return ds
Left err -> M (raise [IncludeParseError err])
-- | Read a file referenced by an include.
readInclude :: Located FilePath -> NoIncM Text
readInclude path = do
file <- fromIncPath (thing path)
source <- T.readFile file `failsWith` handler
return source
where
handler :: X.IOException -> NoIncM a
handler _ = includeFailed path
cryptol-2.4.0/src/Cryptol/Parser/NoPat.hs 0000644 0000000 0000000 00000044064 12737220176 016452 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- The purpose of this module is to convert all patterns to variable
-- patterns. It also eliminates pattern bindings by de-sugaring them
-- into `Bind`. Furthermore, here we associate signatures and pragmas
-- with the names to which they belong.
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.Parser.NoPat (RemovePatterns(..),Error(..)) where
import Cryptol.Parser.AST
import Cryptol.Parser.Position(Range(..),emptyRange,start,at)
import Cryptol.Parser.Names (namesP)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
import MonadLib hiding (mapM)
import Data.Maybe(maybeToList)
import Data.Either(partitionEithers)
import qualified Data.Map as Map
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
class RemovePatterns t where
-- | Eliminate all patterns in a program.
removePatterns :: t -> (t, [Error])
instance RemovePatterns (Program PName) where
removePatterns p = runNoPatM (noPatProg p)
instance RemovePatterns (Expr PName) where
removePatterns e = runNoPatM (noPatE e)
instance RemovePatterns (Module PName) where
removePatterns m = runNoPatM (noPatModule m)
instance RemovePatterns [Decl PName] where
removePatterns ds = runNoPatM (noPatDs ds)
simpleBind :: Located PName -> Expr PName -> Bind PName
simpleBind x e = Bind { bName = x, bParams = []
, bDef = at e (Located emptyRange (DExpr e))
, bSignature = Nothing, bPragmas = []
, bMono = True, bInfix = False, bFixity = Nothing
, bDoc = Nothing
}
sel :: Pattern PName -> PName -> Selector -> Bind PName
sel p x s = let (a,ts) = splitSimpleP p
in simpleBind a (foldl ETyped (ESel (EVar x) s) ts)
-- | Given a pattern, transform it into a simple pattern and a set of bindings.
-- Simple patterns may only contain variables and type annotations.
-- XXX: We can replace the types in the selcetors with annotations on the bindings.
noPat :: Pattern PName -> NoPatM (Pattern PName, [Bind PName])
noPat pat =
case pat of
PVar x -> return (PVar x, [])
PWild ->
do x <- newName
r <- getRange
return (pVar r x, [])
PTuple ps ->
do (as,dss) <- unzip `fmap` mapM noPat ps
x <- newName
r <- getRange
let len = length ps
ty = TTuple (replicate len TWild)
getN a n = sel a x (TupleSel n (Just len))
return (pTy r x ty, zipWith getN as [0..] ++ concat dss)
PList [] ->
do x <- newName
r <- getRange
return (pTy r x (TSeq (TNum 0) TWild), [])
PList ps ->
do (as,dss) <- unzip `fmap` mapM noPat ps
x <- newName
r <- getRange
let len = length ps
ty = TSeq (TNum (fromIntegral len)) TWild
getN a n = sel a x (ListSel n (Just len))
return (pTy r x ty, zipWith getN as [0..] ++ concat dss)
PRecord fs ->
do (as,dss) <- unzip `fmap` mapM (noPat . value) fs
x <- newName
r <- getRange
let shape = map (thing . name) fs
ty = TRecord (map (fmap (\_ -> TWild)) fs)
getN a n = sel a x (RecordSel n (Just shape))
return (pTy r x ty, zipWith getN as shape ++ concat dss)
PTyped p t ->
do (a,ds) <- noPat p
return (PTyped a t, ds)
-- XXX: Ww can do more with type annotations here
PSplit p1 p2 ->
do (a1,ds1) <- noPat p1
(a2,ds2) <- noPat p2
x <- newName
tmp <- newName
r <- getRange
let prim = EVar (mkUnqual (mkIdent "splitAt"))
bTmp = simpleBind (Located r tmp) (EApp prim (EVar x))
b1 = sel a1 tmp (TupleSel 0 (Just 2))
b2 = sel a2 tmp (TupleSel 1 (Just 2))
return (pVar r x, bTmp : b1 : b2 : ds1 ++ ds2)
PLocated p r1 -> inRange r1 (noPat p)
where
pVar r x = PVar (Located r x)
pTy r x t = PTyped (PVar (Located r x)) t
splitSimpleP :: Pattern PName -> (Located PName, [Type PName])
splitSimpleP (PVar x) = (x, [])
splitSimpleP (PTyped p t) = let (x,ts) = splitSimpleP p
in (x, t:ts)
splitSimpleP p = panic "splitSimpleP"
[ "Non-simple pattern", show p ]
--------------------------------------------------------------------------------
noPatE :: Expr PName -> NoPatM (Expr PName)
noPatE expr =
case expr of
EVar {} -> return expr
ELit {} -> return expr
ETuple es -> ETuple <$> mapM noPatE es
ERecord es -> ERecord <$> mapM noPatF es
ESel e s -> ESel <$> noPatE e <*> return s
EList es -> EList <$> mapM noPatE es
EFromTo {} -> return expr
EInfFrom e e' -> EInfFrom <$> noPatE e <*> traverse noPatE e'
EComp e mss -> EComp <$> noPatE e <*> mapM noPatArm mss
EApp e1 e2 -> EApp <$> noPatE e1 <*> noPatE e2
EAppT e ts -> EAppT <$> noPatE e <*> return ts
EIf e1 e2 e3 -> EIf <$> noPatE e1 <*> noPatE e2 <*> noPatE e3
EWhere e ds -> EWhere <$> noPatE e <*> noPatDs ds
ETyped e t -> ETyped <$> noPatE e <*> return t
ETypeVal {} -> return expr
EFun ps e -> do (ps1,e1) <- noPatFun ps e
return (EFun ps1 e1)
ELocated e r1 -> ELocated <$> inRange r1 (noPatE e) <*> return r1
EParens e -> EParens <$> noPatE e
EInfix x y f z-> EInfix <$> noPatE x <*> pure y <*> pure f <*> noPatE z
where noPatF x = do e <- noPatE (value x)
return x { value = e }
noPatFun :: [Pattern PName] -> Expr PName -> NoPatM ([Pattern PName], Expr PName)
noPatFun ps e =
do (xs,bs) <- unzip <$> mapM noPat ps
e1 <- noPatE e
let body = case concat bs of
[] -> e1
ds -> EWhere e1 $ map DBind ds
return (xs, body)
noPatArm :: [Match PName] -> NoPatM [Match PName]
noPatArm ms = concat <$> mapM noPatM ms
noPatM :: Match PName -> NoPatM [Match PName]
noPatM (Match p e) =
do (x,bs) <- noPat p
e1 <- noPatE e
return (Match x e1 : map MatchLet bs)
noPatM (MatchLet b) = (return . MatchLet) <$> noMatchB b
noMatchB :: Bind PName -> NoPatM (Bind PName)
noMatchB b =
case thing (bDef b) of
DPrim | null (bParams b) -> return b
| otherwise -> panic "NoPat" [ "noMatchB: primitive with params"
, show b ]
DExpr e ->
do (ps,e') <- noPatFun (bParams b) e
return b { bParams = ps, bDef = DExpr e' <$ bDef b }
noMatchD :: Decl PName -> NoPatM [Decl PName]
noMatchD decl =
case decl of
DSignature {} -> return [decl]
DPragma {} -> return [decl]
DFixity{} -> return [decl]
DBind b -> do b1 <- noMatchB b
return [DBind b1]
DPatBind p e -> do (p',bs) <- noPat p
let (x,ts) = splitSimpleP p'
e1 <- noPatE e
let e2 = foldl ETyped e1 ts
return $ DBind Bind { bName = x
, bParams = []
, bDef = at e (Located emptyRange (DExpr e2))
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
} : map DBind bs
DType {} -> return [decl]
DLocated d r1 -> do bs <- inRange r1 $ noMatchD d
return $ map (`DLocated` r1) bs
noPatDs :: [Decl PName] -> NoPatM [Decl PName]
noPatDs ds =
do ds1 <- concat <$> mapM noMatchD ds
let pragmaMap = Map.fromListWith (++) $ concatMap toPragma ds1
sigMap = Map.fromListWith (++) $ concatMap toSig ds1
fixMap = Map.fromListWith (++) $ concatMap toFixity ds1
(ds2, (pMap,sMap,fMap,_)) <- runStateT (pragmaMap, sigMap, fixMap, Map.empty)
(annotDs ds1)
forM_ (Map.toList pMap) $ \(n,ps) ->
forM_ ps $ \p -> recordError $ PragmaNoBind (p { thing = n }) (thing p)
forM_ (Map.toList sMap) $ \(n,ss) ->
do _ <- checkSigs n ss
forM_ ss $ \s -> recordError $ SignatureNoBind (s { thing = n })
(thing s)
forM_ (Map.toList fMap) $ \(n,fs) ->
forM_ fs $ \f -> recordError $ FixityNoBind f { thing = n }
return ds2
noPatTopDs :: [TopLevel (Decl PName)] -> NoPatM [TopLevel (Decl PName)]
noPatTopDs tds =
do noPatGroups <- mapM (noMatchD . tlValue) tds
let allDecls = concat noPatGroups
pragmaMap = Map.fromListWith (++) $ concatMap toPragma allDecls
sigMap = Map.fromListWith (++) $ concatMap toSig allDecls
fixMap = Map.fromListWith (++) $ concatMap toFixity allDecls
docMap = Map.fromListWith (++) $ concatMap toDocs tds
let exportGroups = zipWith (\ td ds -> td { tlValue = ds }) tds noPatGroups
(tds', (pMap,sMap,fMap,_)) <- runStateT (pragmaMap,sigMap,fixMap,docMap)
(annotTopDs exportGroups)
forM_ (Map.toList pMap) $ \(n,ps) ->
forM_ ps $ \p -> recordError $ PragmaNoBind (p { thing = n }) (thing p)
forM_ (Map.toList sMap) $ \(n,ss) ->
do _ <- checkSigs n ss
forM_ ss $ \s -> recordError $ SignatureNoBind (s { thing = n })
(thing s)
forM_ (Map.toList fMap) $ \(n,fs) ->
forM_ fs $ \f -> recordError $ FixityNoBind f { thing = n }
return tds'
noPatProg :: Program PName -> NoPatM (Program PName)
noPatProg (Program topDs) =
do let (ds, others) = partitionEithers (map isDecl topDs)
ds1 <- noPatTopDs ds
return $ Program $ others ++ map Decl ds1
where
isDecl (Decl d) = Left d
isDecl d = Right d
noPatModule :: Module PName -> NoPatM (Module PName)
noPatModule m =
do let (ds, others) = partitionEithers (map isDecl (mDecls m))
ds1 <- noPatTopDs ds
return m { mDecls = others ++ map Decl ds1 }
where
isDecl (Decl d) = Left d
isDecl d = Right d
--------------------------------------------------------------------------------
type AnnotMap = ( Map.Map PName [Located Pragma ]
, Map.Map PName [Located (Schema PName)]
, Map.Map PName [Located Fixity ]
, Map.Map PName [Located String ]
)
-- | Add annotations to exported declaration groups.
--
-- XXX: This isn't quite right: if a signature and binding have different
-- export specifications, this will favor the specification of the binding.
-- This is most likely the intended behavior, so it's probably fine, but it does
-- smell a bit.
annotTopDs :: [TopLevel [Decl PName]]
-> StateT AnnotMap NoPatM [TopLevel (Decl PName)]
annotTopDs tds =
case tds of
(ds:dss) ->
do ds' <- annotDs (tlValue ds)
rest <- annotTopDs dss
if null ds'
then return rest
else return ([ ds { tlValue = d } | d <- ds' ] ++ rest)
[] -> return []
-- | Add annotations, keeping track of which annotation are not yet used up.
annotDs :: [Decl PName] -> StateT AnnotMap NoPatM [Decl PName]
annotDs (d : ds) =
do ignore <- runExceptionT (annotD d)
case ignore of
Left () -> annotDs ds
Right d1 -> (d1 :) <$> annotDs ds
annotDs [] = return []
-- | Add annotations, keeping track of which annotation are not yet used up.
-- The exception indicates which declarations are no longer needed.
annotD :: Decl PName -> ExceptionT () (StateT AnnotMap NoPatM) (Decl PName)
annotD decl =
case decl of
DBind b -> DBind <$> lift (annotB b)
DSignature {} -> raise ()
DFixity{} -> raise ()
DPragma {} -> raise ()
DPatBind {} -> raise ()
DType {} -> return decl
DLocated d r -> (`DLocated` r) <$> annotD d
-- | Add pragma/signature annotations to a binding.
annotB :: Bind PName -> StateT AnnotMap NoPatM (Bind PName)
annotB Bind { .. } =
do (ps,ss,fs,ds) <- get
let name = thing bName
remove _ _ = Nothing
case ( Map.updateLookupWithKey remove name ps
, Map.updateLookupWithKey remove name ss
, Map.updateLookupWithKey remove name fs
, Map.updateLookupWithKey remove name ds
) of
( (thisPs, pragmas1), (thisSigs, sigs1), (thisFixes, fixes1), (thisDocs, docs1)) ->
do s <- lift $ checkSigs name (jn thisSigs)
f <- lift $ checkFixs name (jn thisFixes)
d <- lift $ checkDocs name (jn thisDocs)
set (pragmas1,sigs1,fixes1,docs1)
return Bind { bSignature = s
, bPragmas = map thing (jn thisPs) ++ bPragmas
, bFixity = f
, bDoc = d
, ..
}
where jn x = concat (maybeToList x)
-- | Check for multiple signatures.
checkSigs :: PName -> [Located (Schema PName)] -> NoPatM (Maybe (Schema PName))
checkSigs _ [] = return Nothing
checkSigs _ [s] = return (Just (thing s))
checkSigs f xs@(s : _ : _) = do recordError $ MultipleSignatures f xs
return (Just (thing s))
checkFixs :: PName -> [Located Fixity] -> NoPatM (Maybe Fixity)
checkFixs _ [] = return Nothing
checkFixs _ [f] = return (Just (thing f))
checkFixs f fs@(x:_) = do recordError $ MultipleFixities f $ map srcRange fs
return (Just (thing x))
checkDocs :: PName -> [Located String] -> NoPatM (Maybe String)
checkDocs _ [] = return Nothing
checkDocs _ [d] = return (Just (thing d))
checkDocs f ds@(d:_) = do recordError $ MultipleDocs f (map srcRange ds)
return (Just (thing d))
-- | Does this declaration provide some signatures?
toSig :: Decl PName -> [(PName, [Located (Schema PName)])]
toSig (DLocated d _) = toSig d
toSig (DSignature xs s) = [ (thing x,[Located (srcRange x) s]) | x <- xs ]
toSig _ = []
-- | Does this declaration provide some signatures?
toPragma :: Decl PName -> [(PName, [Located Pragma])]
toPragma (DLocated d _) = toPragma d
toPragma (DPragma xs s) = [ (thing x,[Located (srcRange x) s]) | x <- xs ]
toPragma _ = []
-- | Does this declaration provide fixity information?
toFixity :: Decl PName -> [(PName, [Located Fixity])]
toFixity (DFixity f ns) = [ (thing n, [Located (srcRange n) f]) | n <- ns ]
toFixity _ = []
-- | Does this top-level declaration provide a documentation string?
toDocs :: TopLevel (Decl PName) -> [(PName, [Located String])]
toDocs TopLevel { .. }
| Just txt <- tlDoc = go txt tlValue
| otherwise = []
where
go txt decl =
case decl of
DSignature ns _ -> [ (thing n, [txt]) | n <- ns ]
DFixity _ ns -> [ (thing n, [txt]) | n <- ns ]
DBind b -> [ (thing (bName b), [txt]) ]
DLocated d _ -> go txt d
DPatBind p _ -> [ (thing n, [txt]) | n <- namesP p ]
-- XXX revisit these
DPragma _ _ -> []
DType _ -> []
--------------------------------------------------------------------------------
newtype NoPatM a = M { unM :: ReaderT Range (StateT RW Id) a }
data RW = RW { names :: !Int, errors :: [Error] }
data Error = MultipleSignatures PName [Located (Schema PName)]
| SignatureNoBind (Located PName) (Schema PName)
| PragmaNoBind (Located PName) Pragma
| MultipleFixities PName [Range]
| FixityNoBind (Located PName)
| MultipleDocs PName [Range]
deriving (Show,Generic, NFData)
instance Functor NoPatM where fmap = liftM
instance Applicative NoPatM where pure = return; (<*>) = ap
instance Monad NoPatM where
return x = M (return x)
fail x = M (fail x)
M x >>= k = M (x >>= unM . k)
-- | Pick a new name, to be used when desugaring patterns.
newName :: NoPatM PName
newName = M $ sets $ \s -> let x = names s
in (NewName NoPat x, s { names = x + 1 })
-- | Record an error.
recordError :: Error -> NoPatM ()
recordError e = M $ sets_ $ \s -> s { errors = e : errors s }
getRange :: NoPatM Range
getRange = M ask
inRange :: Range -> NoPatM a -> NoPatM a
inRange r m = M $ local r $ unM m
runNoPatM :: NoPatM a -> (a, [Error])
runNoPatM m
= getErrs
$ runId
$ runStateT RW { names = 0, errors = [] }
$ runReaderT (Range start start "") -- hm
$ unM m
where getErrs (a,rw) = (a, errors rw)
--------------------------------------------------------------------------------
instance PP Error where
ppPrec _ err =
case err of
MultipleSignatures x ss ->
text "Multiple type signatures for" <+> quotes (pp x)
$$ nest 2 (vcat (map pp ss))
SignatureNoBind x s ->
text "At" <+> pp (srcRange x) <> colon <+>
text "Type signature without a matching binding:"
$$ nest 2 (pp s)
PragmaNoBind x s ->
text "At" <+> pp (srcRange x) <> colon <+>
text "Pragma without a matching binding:"
$$ nest 2 (pp s)
MultipleFixities n locs ->
text "Multiple fixity declarations for" <+> quotes (pp n)
$$ nest 2 (vcat (map pp locs))
FixityNoBind n ->
text "At" <+> pp (srcRange n) <> colon <+>
text "Fixity declaration without a matching binding for:" <+>
pp (thing n)
MultipleDocs n locs ->
text "Multiple documentation blocks given for:" <+> pp n
$$ nest 2 (vcat (map pp locs))
cryptol-2.4.0/src/Cryptol/Parser/ParserUtils.hs 0000644 0000000 0000000 00000036665 12737220176 017716 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.Parser.ParserUtils where
import Cryptol.Parser.AST
import Cryptol.Parser.Lexer
import Cryptol.Parser.Position
import Cryptol.Parser.Utils (translateExprToNumT,widthIdent)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic
import Data.Maybe(listToMaybe,fromMaybe)
import Data.Bits(testBit,setBit)
import Control.Monad(liftM,ap,unless)
import qualified Data.Text as S
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
parseString :: Config -> ParseM a -> String -> Either ParseError a
parseString cfg p cs = parse cfg p (T.pack cs)
parse :: Config -> ParseM a -> Text -> Either ParseError a
parse cfg p cs = case unP p cfg eofPos (S toks) of
Left err -> Left err
Right (a,_) -> Right a
where (toks,eofPos) = lexer cfg cs
{- The parser is parameterized by the pozition of the final token. -}
data ParseM a = P { unP :: Config -> Position -> S -> Either ParseError (a,S) }
lexerP :: (Located Token -> ParseM a) -> ParseM a
lexerP k = P $ \cfg p (S ts) ->
case ts of
t : _ | Err e <- tokenType it ->
Left $ HappyErrorMsg (srcRange t) $
case e of
UnterminatedComment -> "unterminated comment"
UnterminatedString -> "unterminated string"
UnterminatedChar -> "unterminated character"
InvalidString -> "invalid string literal: " ++ T.unpack (tokenText it)
InvalidChar -> "invalid character literal: " ++ T.unpack (tokenText it)
LexicalError -> "unrecognized character: " ++ T.unpack (tokenText it)
where it = thing t
t : more -> unP (k t) cfg p (S more)
[] -> Left (HappyError (cfgSource cfg) p Nothing)
data ParseError = HappyError FilePath Position (Maybe Token)
| HappyErrorMsg Range String
deriving (Show, Generic, NFData)
newtype S = S [Located Token]
instance PP ParseError where
ppPrec _ (HappyError _ _ tok) = case tok of
Nothing -> text "end of input"
Just t -> pp t
ppPrec _ (HappyErrorMsg _ x) = text x
ppError :: ParseError -> Doc
ppError (HappyError path pos (Just tok))
| Err _ <- tokenType tok = text "Parse error at" <+>
text path <> char ':' <> pp pos <> comma <+>
pp tok
ppError e@(HappyError path pos _) =
text "Parse error at" <+>
text path <> char ':' <> pp pos <> comma <+>
text "unexpected" <+> pp e
ppError (HappyErrorMsg p x) = text "Parse error at" <+> pp p $$ nest 2 (text x)
instance Monad ParseM where
return a = P (\_ _ s -> Right (a,s))
fail s = panic "[Parser] fail" [s]
m >>= k = P (\cfg p s1 -> case unP m cfg p s1 of
Left e -> Left e
Right (a,s2) -> unP (k a) cfg p s2)
instance Functor ParseM where
fmap = liftM
instance Applicative ParseM where
pure = return
(<*>) = ap
happyError :: ParseM a
happyError = P $ \cfg p (S ls) ->
Left $ case listToMaybe ls of
Nothing -> HappyError (cfgSource cfg) p Nothing
Just l -> HappyError (cfgSource cfg) (from (srcRange l)) (Just (thing l))
errorMessage :: Range -> String -> ParseM a
errorMessage r x = P $ \_ _ _ -> Left (HappyErrorMsg r x)
customError :: String -> Located Token -> ParseM a
customError x t = P $ \_ _ _ -> Left (HappyErrorMsg (srcRange t) x)
mkModName :: [T.Text] -> ModName
mkModName strs = T.toStrict (T.intercalate (T.pack "::") strs)
-- Note that type variables are not resolved at this point: they are tcons.
mkSchema :: [TParam PName] -> [Prop PName] -> Type PName -> Schema PName
mkSchema xs ps t = Forall xs ps t Nothing
getName :: Located Token -> PName
getName l = case thing l of
Token (Ident [] x) _ -> mkUnqual (mkIdent (T.toStrict x))
_ -> panic "[Parser] getName" ["not an Ident:", show l]
getNum :: Located Token -> Integer
getNum l = case thing l of
Token (Num x _ _) _ -> x
Token (ChrLit x) _ -> fromIntegral (fromEnum x)
_ -> panic "[Parser] getNum" ["not a number:", show l]
getStr :: Located Token -> String
getStr l = case thing l of
Token (StrLit x) _ -> x
_ -> panic "[Parser] getStr" ["not a string:", show l]
numLit :: TokenT -> Expr PName
numLit (Num x base digs)
| base == 2 = ELit $ ECNum x (BinLit digs)
| base == 8 = ELit $ ECNum x (OctLit digs)
| base == 10 = ELit $ ECNum x DecLit
| base == 16 = ELit $ ECNum x (HexLit digs)
numLit x = panic "[Parser] numLit" ["invalid numeric literal", show x]
intVal :: Located Token -> ParseM Integer
intVal tok =
case tokenType (thing tok) of
Num x _ _ -> return x
_ -> errorMessage (srcRange tok) "Expected an integer"
mkFixity :: Assoc -> Located Token -> [LPName] -> ParseM (Decl PName)
mkFixity assoc tok qns =
do l <- intVal tok
unless (l >= 1 && l <= 100)
(errorMessage (srcRange tok) "Fixity levels must be between 0 and 20")
return (DFixity (Fixity assoc (fromInteger l)) qns)
mkTupleSel :: Range -> Integer -> ParseM (Located Selector)
mkTupleSel pos n
| n < 0 = errorMessage pos
(show n ++ " is not a valid tuple selector (they start from 0).")
| toInteger asInt /= n = errorMessage pos "Tuple selector is too large."
| otherwise = return $ Located pos $ TupleSel asInt Nothing
where asInt = fromInteger n
fromStrLit :: Located Token -> ParseM (Located String)
fromStrLit loc = case tokenType (thing loc) of
StrLit str -> return loc { thing = str }
_ -> errorMessage (srcRange loc) "Expected a string literal"
validDemotedType :: Range -> Type PName -> ParseM (Type PName)
validDemotedType rng ty =
case ty of
TLocated t r -> validDemotedType r t
TRecord {} -> bad "Record types"
TTuple {} -> bad "Tuple types"
TFun {} -> bad "Function types"
TSeq {} -> bad "Sequence types"
TBit -> bad "Type bit"
TNum {} -> ok
TChar {} -> ok
TInf -> bad "Infinity type"
TWild -> bad "Wildcard types"
TUser {} -> ok
TApp {} -> ok
TParens t -> validDemotedType rng t
TInfix{} -> ok
where bad x = errorMessage rng (x ++ " cannot be demoted.")
ok = return $ at rng ty
mkEApp :: [Expr PName] -> Expr PName
mkEApp es@(eLast : _) = at (eFirst,eLast) $ foldl EApp f xs
where
eFirst : rest = reverse es
f : xs = cvtTypeParams eFirst rest
{- Type applications are parsed as `ETypeVal (TRecord fs)` expressions.
Here we associate them with their corresponding functions,
converting them into `EAppT` constructs. For example:
[ f, x, `{ a = 2 }, y ]
becomes
[ f, x ` { a = 2 }, y ]
-}
cvtTypeParams e [] = [e]
cvtTypeParams e (p : ps) =
case toTypeParam p of
Just fs -> cvtTypeParams (EAppT e fs) ps
Nothing -> e : cvtTypeParams p ps
toTypeParam e =
case dropLoc e of
ETypeVal t -> case dropLoc t of
TRecord fs -> Just (map mkTypeInst fs)
_ -> Nothing
_ -> Nothing
mkEApp es = panic "[Parser] mkEApp" ["Unexpected:", show es]
unOp :: Expr PName -> Expr PName -> Expr PName
unOp f x = at (f,x) $ EApp f x
-- Use defaultFixity as a placeholder, it will be fixed during renaming.
binOp :: Expr PName -> Located PName -> Expr PName -> Expr PName
binOp x f y = at (x,y) $ EInfix x f defaultFixity y
eFromTo :: Range -> Expr PName -> Maybe (Expr PName) -> Maybe (Expr PName) -> ParseM (Expr PName)
eFromTo r e1 e2 e3 = EFromTo <$> exprToNumT r e1
<*> mapM (exprToNumT r) e2
<*> mapM (exprToNumT r) e3
exprToNumT :: Range -> Expr PName -> ParseM (Type PName)
exprToNumT r expr =
case translateExprToNumT expr of
Just t -> return t
Nothing -> bad
where
bad = errorMessage (fromMaybe r (getLoc expr)) $ unlines
[ "The boundaries of .. sequences should be valid numeric types."
, "The expression `" ++ show (pp expr) ++ "` is not."
, ""
, "If you were trying to specify the width of the elements,"
, "you may add a type annotation outside the sequence. For example:"
, " [ 1 .. 10 ] : [_][16]"
]
-- | WARNING: This is a bit of a hack.
-- It is used to represent anonymous type applications.
anonRecord :: Maybe Range -> [Type PName] -> Type PName
anonRecord ~(Just r) ts = TRecord (map toField ts)
where noName = Located { srcRange = r, thing = mkIdent (S.pack "") }
toField t = Named { name = noName, value = t }
exportDecl :: Maybe (Located String) -> ExportType -> Decl PName -> TopDecl PName
exportDecl mbDoc e d = Decl TopLevel { tlExport = e
, tlDoc = mbDoc
, tlValue = d }
exportNewtype :: ExportType -> Newtype PName -> TopDecl PName
exportNewtype e n = TDNewtype TopLevel { tlExport = e
, tlDoc = Nothing
, tlValue = n }
changeExport :: ExportType -> [TopDecl PName] -> [TopDecl PName]
changeExport e = map change
where
change (Decl d) = Decl d { tlExport = e }
change (TDNewtype n) = TDNewtype n { tlExport = e }
change td@Include{} = td
mkTypeInst :: Named (Type PName) -> TypeInst PName
mkTypeInst x | nullIdent (thing (name x)) = PosInst (value x)
| otherwise = NamedInst x
mkTParam :: Located Ident -> Maybe Kind -> ParseM (TParam PName)
mkTParam Located { srcRange = rng, thing = n } k
| n == widthIdent = errorMessage rng "`width` is not a valid type parameter name."
| otherwise = return (TParam (mkUnqual n) k (Just rng))
mkTySyn :: Located PName -> [TParam PName] -> Type PName -> ParseM (Decl PName)
mkTySyn ln ps b
| getIdent (thing ln) == widthIdent =
errorMessage (srcRange ln) "`width` is not a valid type synonym name."
| otherwise =
return $ DType $ TySyn ln ps b
polyTerm :: Range -> Integer -> Integer -> ParseM (Bool, Integer)
polyTerm rng k p
| k == 0 = return (False, p)
| k == 1 = return (True, p)
| otherwise = errorMessage rng "Invalid polynomial coefficient"
mkPoly :: Range -> [ (Bool,Integer) ] -> ParseM (Expr PName)
mkPoly rng terms = mk 0 (map fromInteger bits)
where
w = case terms of
[] -> 0
_ -> 1 + maximum (map (fromInteger . snd) terms)
bits = [ n | (True,n) <- terms ]
mk res [] = return $ ELit $ ECNum res (PolyLit w)
mk res (n : ns)
| testBit res n = errorMessage rng
("Polynomial contains multiple terms with exponent "
++ show n)
| otherwise = mk (setBit res n) ns
-- NOTE: The list of patterns is reversed!
mkProperty :: LPName -> [Pattern PName] -> Expr PName -> Decl PName
mkProperty f ps e = DBind Bind { bName = f
, bParams = reverse ps
, bDef = at e (Located emptyRange (DExpr (ETyped e TBit)))
, bSignature = Nothing
, bPragmas = [PragmaProperty]
, bMono = False
, bInfix = False
, bFixity = Nothing
, bDoc = Nothing
}
mkIf :: [(Expr PName, Expr PName)] -> Expr PName -> Expr PName
mkIf ifThens theElse = foldr addIfThen theElse ifThens
where
addIfThen (cond, doexpr) elseExpr = EIf cond doexpr elseExpr
-- | Generate a signature and a primitive binding. The reason for generating
-- both instead of just adding the signature at this point is that it means the
-- primitive declarations don't need to be treated differently in the noPat
-- pass. This is also the reason we add the doc to the TopLevel constructor,
-- instead of just place it on the binding directly. A better solution might be
-- to just have a different constructor for primitives.
mkPrimDecl :: Maybe (Located String) -> LPName -> Schema PName -> [TopDecl PName]
mkPrimDecl mbDoc ln sig =
[ exportDecl mbDoc Public
$ DBind Bind { bName = ln
, bParams = []
, bDef = at sig (Located emptyRange DPrim)
, bSignature = Nothing
, bPragmas = []
, bMono = False
, bInfix = isInfixIdent (getIdent (thing ln))
, bFixity = Nothing
, bDoc = Nothing
}
, exportDecl Nothing Public
$ DSignature [ln] sig
]
-- | Fix-up the documentation strings by removing the comment delimiters on each
-- end, and stripping out common prefixes on all the remaining lines.
mkDoc :: Located Text -> Located String
mkDoc ltxt = ltxt { thing = docStr }
where
docStr = unlines
$ map T.unpack
$ dropPrefix
$ trimFront
$ T.lines
$ T.dropWhileEnd (`elem` "/* \r\n\t")
$ thing ltxt
trimFront [] = []
trimFront (l:ls)
| T.all (`elem` "/* \r\n\t") l = ls
| otherwise = T.dropWhile (`elem` "/* ") l : ls
dropPrefix [] = []
dropPrefix [t] = [T.dropWhile (`elem` "/* ") t]
dropPrefix ts@(l:ls) =
case T.uncons l of
Just (c,_) | all (commonPrefix c) ls -> dropPrefix (map (T.drop 1) ts)
_ -> ts
where
commonPrefix c t =
case T.uncons t of
Just (c',_) -> c == c'
Nothing -> False
mkProp :: Type PName -> ParseM (Located [Prop PName])
mkProp ty =
case ty of
TLocated t r -> Located r `fmap` props r t
_ -> panic "Parser" [ "Invalid type given to mkProp"
, "expected a location"
, show ty ]
where
props r t =
case t of
TInfix{} -> infixProp t
TUser f xs -> prefixProp r f xs
TTuple ts -> concat `fmap` mapM (props r) ts
TParens t' -> props r t'
TLocated t' r' -> props r' t'
TApp{} -> err
TFun{} -> err
TSeq{} -> err
TBit{} -> err
TNum{} -> err
TChar{} -> err
TInf{} -> err
TWild -> err
TRecord{} -> err
where
err = errorMessage r "Invalid constraint"
-- we have to delay these until renaming, when we have the fixity table
-- present
infixProp t = return [CType t]
-- these can be translated right away
prefixProp r f xs
| i == arithIdent, [x] <- xs = return [CLocated (CArith x) r]
| i == finIdent, [x] <- xs = return [CLocated (CFin x) r]
| i == cmpIdent, [x] <- xs = return [CLocated (CCmp x) r]
| otherwise = errorMessage r "Invalid constraint"
where
i = getIdent f
arithIdent, finIdent, cmpIdent :: Ident
arithIdent = mkIdent (S.pack "Arith")
finIdent = mkIdent (S.pack "fin")
cmpIdent = mkIdent (S.pack "Cmp")
cryptol-2.4.0/src/Cryptol/Parser/Position.hs 0000644 0000000 0000000 00000006633 12737220176 017235 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.Parser.Position where
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import GHC.Generics (Generic)
import Control.DeepSeq
import Cryptol.Utils.PP
data Located a = Located { srcRange :: !Range, thing :: a }
deriving (Eq, Show, Generic, NFData)
data Position = Position { line :: !Int, col :: !Int }
deriving (Eq, Ord, Show, Generic, NFData)
data Range = Range { from :: !Position
, to :: !Position
, source :: FilePath }
deriving (Eq, Show, Generic, NFData)
-- | An empty range.
--
-- Caution: using this on the LHS of a use of rComb will cause the empty source
-- to propegate.
emptyRange :: Range
emptyRange = Range { from = start, to = start, source = "" }
start :: Position
start = Position { line = 1, col = 1 }
move :: Position -> Char -> Position
move p c = case c of
'\t' -> p { col = ((col p + 7) `div` 8) * 8 + 1 }
'\n' -> p { col = 1, line = 1 + line p }
_ -> p { col = 1 + col p }
moves :: Position -> Text -> Position
moves p cs = T.foldl' move p cs
rComb :: Range -> Range -> Range
rComb r1 r2 = Range { from = rFrom, to = rTo, source = source r1 }
where rFrom = min (from r1) (from r2)
rTo = max (to r1) (to r2)
rCombs :: [Range] -> Range
rCombs = foldl1 rComb
instance Functor Located where
fmap f l = l { thing = f (thing l) }
--------------------------------------------------------------------------------
instance PP Position where
ppPrec _ p = int (line p) <> colon <> int (col p)
instance PP Range where
ppPrec _ r = text (source r) <> char ':'
<> pp (from r) <> text "--" <> pp (to r)
instance PP a => PP (Located a) where
ppPrec _ l = parens (text "at" <+> pp (srcRange l) <> comma <+> pp (thing l))
instance PPName a => PPName (Located a) where
ppNameFixity Located { .. } = ppNameFixity thing
ppPrefixName Located { .. } = ppPrefixName thing
ppInfixName Located { .. } = ppInfixName thing
--------------------------------------------------------------------------------
class HasLoc t where
getLoc :: t -> Maybe Range
instance HasLoc Range where
getLoc r = Just r
instance HasLoc (Located a) where
getLoc r = Just (srcRange r)
instance (HasLoc a, HasLoc b) => HasLoc (a,b) where
getLoc (f,t) = case getLoc f of
Nothing -> getLoc t
Just l ->
case getLoc t of
Nothing -> return l
Just l1 -> return (rComb l l1)
instance HasLoc a => HasLoc [a] where
getLoc = go Nothing
where
go x [] = x
go Nothing (x : xs) = go (getLoc x) xs
go (Just l) (x : xs) = case getLoc x of
Nothing -> go (Just l) xs
Just l1 -> go (Just (rComb l l1)) xs
class HasLoc t => AddLoc t where
addLoc :: t -> Range -> t
dropLoc :: t -> t
instance AddLoc (Located a) where
addLoc t r = t { srcRange = r }
dropLoc r = r
at :: (HasLoc l, AddLoc t) => l -> t -> t
at l e = maybe e (addLoc e) (getLoc l)
cryptol-2.4.0/src/Cryptol/Parser/Unlit.hs 0000644 0000000 0000000 00000007463 12737220176 016526 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Convert a literate source file into an ordinary source file.
{-# LANGUAGE OverloadedStrings, Safe, PatternGuards #-}
module Cryptol.Parser.Unlit
( unLit, PreProc(..), guessPreProc, knownExts
) where
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as Text
import Data.Char(isSpace)
import System.FilePath(takeExtension)
import Cryptol.Utils.Panic
data PreProc = None | Markdown | LaTeX
knownExts :: [String]
knownExts =
[ "cry"
, "tex"
, "markdown"
, "md"
]
guessPreProc :: FilePath -> PreProc
guessPreProc file = case takeExtension file of
".tex" -> LaTeX
".markdown" -> Markdown
".md" -> Markdown
_ -> None
unLit :: PreProc -> Text -> Text
unLit None = id
unLit proc = Text.unlines . concatMap toCryptol . preProc proc . Text.lines
preProc :: PreProc -> [Text] -> [Block]
preProc p =
case p of
None -> return . Code
Markdown -> markdown
LaTeX -> latex
data Block = Code [Text] | Comment [Text]
toCryptol :: Block -> [Text]
toCryptol (Code xs) = xs
toCryptol (Comment ls) =
case ls of
[] -> []
[l] -> [ "/* " `Text.append` l `Text.append` " */" ]
l1 : rest -> let (more, l) = splitLast rest
in "/* " `Text.append` l1 : more ++ [ l `Text.append` " */" ]
where
splitLast [] = panic "Cryptol.Parser.Unlit.toCryptol" [ "splitLast []" ]
splitLast [x] = ([], x)
splitLast (x : xs) = let (ys,y) = splitLast xs
in (x:ys,y)
mk :: ([Text] -> Block) -> [Text] -> [Block]
mk _ [] = []
mk c ls = [ c (reverse ls) ]
-- | The preprocessor for `markdown`
markdown :: [Text] -> [Block]
markdown = blanks []
where
comment current [] = mk Comment current
comment current (l : ls)
| isBlank l = blanks (l : current) ls
| otherwise = comment (l : current) ls
blanks current [] = mk Comment current
blanks current (l : ls)
| isCodeLine l = mk Comment current ++ code [l] ls
| Just op <- isOpenFence l = mk Comment (l : current) ++ fenced op [] ls
| isBlank l = blanks (l : current) ls
| otherwise = comment (l : current) ls
code current [] = mk Code current
code current (l : ls)
| isCodeLine l = code (l : current) ls
| otherwise = mk Code current ++ comment [] (l : ls)
fenced op current [] = mk op current -- XXX should this be an error?
fenced op current (l : ls)
| isCloseFence l = mk op current ++ comment [l] ls
| otherwise = fenced op (l : current) ls
isOpenFence l | "```cryptol" == l' = Just Code
| "```" == l' = Just Code
| "```" `Text.isPrefixOf` l' = Just Comment
| otherwise = Nothing
where
l' = Text.dropWhile isSpace l
isCloseFence l = "```" `Text.isPrefixOf` l
isBlank l = Text.all isSpace l
isCodeLine l = "\t" `Text.isPrefixOf` l || " " `Text.isPrefixOf` l
-- | The preprocessor for `latex`
latex :: [Text] -> [Block]
latex = comment []
where
comment current [] = mk Comment current
comment current (l : ls)
| isBeginCode l = mk Comment (l : current) ++ code [] ls
| otherwise = comment (l : current) ls
code current [] = mk Code current
code current (l : ls)
| isEndCode l = mk Code current ++ comment [l] ls
| otherwise = code (l : current) ls
isBeginCode l = "\\begin{code}" `Text.isPrefixOf` l
isEndCode l = "\\end{code}" `Text.isPrefixOf` l
cryptol-2.4.0/src/Cryptol/Parser/Utils.hs 0000644 0000000 0000000 00000003065 12737220176 016525 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Utility functions that are also useful for translating programs
-- from previous Cryptol versions.
{-# LANGUAGE OverloadedStrings #-}
module Cryptol.Parser.Utils
( translateExprToNumT
, widthIdent
) where
import Cryptol.Parser.AST
import Cryptol.Prims.Syntax
widthIdent :: Ident
widthIdent = mkIdent "width"
translateExprToNumT :: Expr PName -> Maybe (Type PName)
translateExprToNumT expr =
case expr of
ELocated e r -> (`TLocated` r) `fmap` translateExprToNumT e
EVar n | getIdent n == widthIdent -> mkFun TCWidth
EVar x -> return (TUser x [])
ELit x -> cvtLit x
EApp e1 e2 -> do t1 <- translateExprToNumT e1
t2 <- translateExprToNumT e2
tApp t1 t2
EInfix a o f b -> do e1 <- translateExprToNumT a
e2 <- translateExprToNumT b
return (TInfix e1 o f e2)
EParens e -> translateExprToNumT e
_ -> Nothing
where
tApp ty t =
case ty of
TLocated t1 r -> (`TLocated` r) `fmap` tApp t1 t
TApp f ts -> return (TApp f (ts ++ [t]))
TUser f ts -> return (TUser f (ts ++ [t]))
_ -> Nothing
mkFun f = return (TApp f [])
cvtLit (ECNum n CharLit) = return (TChar $ toEnum $ fromInteger n)
cvtLit (ECNum n _) = return (TNum n)
cvtLit (ECString _) = Nothing
cryptol-2.4.0/src/Cryptol/Prims/ 0000755 0000000 0000000 00000000000 12737220176 014723 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Prims/Eval.hs 0000644 0000000 0000000 00000055476 12737220176 016167 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BangPatterns #-}
module Cryptol.Prims.Eval where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat (Nat'(..),fromNat,genLog, nMul)
import qualified Cryptol.Eval.Arch as Arch
import Cryptol.Eval.Error
import Cryptol.Eval.Type(evalTF)
import Cryptol.Eval.Value
import Cryptol.Testing.Random (randomValue)
import Cryptol.Utils.Panic (panic)
import Cryptol.ModuleSystem.Name (asPrim)
import Cryptol.Utils.Ident (Ident,mkIdent)
import Data.List (sortBy, transpose, genericTake, genericDrop,
genericReplicate, genericSplitAt, genericIndex)
import Data.Ord (comparing)
import Data.Bits (Bits(..))
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import System.Random.TF.Gen (seedTFGen)
-- Primitives ------------------------------------------------------------------
evalPrim :: Decl -> Value
evalPrim Decl { dName = n, .. }
| Just prim <- asPrim n, Just val <- Map.lookup prim primTable = val
evalPrim Decl { .. } =
panic "Eval" [ "Unimplemented primitive", show dName ]
primTable :: Map.Map Ident Value
primTable = Map.fromList $ map (\(n, v) -> (mkIdent (T.pack n), v))
[ ("+" , binary (arithBinary (liftBinArith (+))))
, ("-" , binary (arithBinary (liftBinArith (-))))
, ("*" , binary (arithBinary (liftBinArith (*))))
, ("/" , binary (arithBinary (liftBinArith divWrap)))
, ("%" , binary (arithBinary (liftBinArith modWrap)))
, ("^^" , binary (arithBinary modExp))
, ("lg2" , unary (arithUnary lg2))
, ("negate" , unary (arithUnary negate))
, ("<" , binary (cmpOrder (\o -> o == LT )))
, (">" , binary (cmpOrder (\o -> o == GT )))
, ("<=" , binary (cmpOrder (\o -> o == LT || o == EQ)))
, (">=" , binary (cmpOrder (\o -> o == GT || o == EQ)))
, ("==" , binary (cmpOrder (\o -> o == EQ)))
, ("!=" , binary (cmpOrder (\o -> o /= EQ)))
, ("&&" , binary (logicBinary (.&.)))
, ("||" , binary (logicBinary (.|.)))
, ("^" , binary (logicBinary xor))
, ("complement" , unary (logicUnary complement))
, ("<<" , logicShift shiftLW shiftLS)
, (">>" , logicShift shiftRW shiftRS)
, ("<<<" , logicShift rotateLW rotateLS)
, (">>>" , logicShift rotateRW rotateRS)
, ("True" , VBit True)
, ("False" , VBit False)
, ("demote" , ecDemoteV)
, ("#" , nlam $ \ front ->
nlam $ \ back ->
tlam $ \ elty ->
lam $ \ l ->
lam $ \ r -> ccatV front back elty l r)
, ("@" , indexPrimOne indexFront)
, ("@@" , indexPrimMany indexFrontRange)
, ("!" , indexPrimOne indexBack)
, ("!!" , indexPrimMany indexBackRange)
, ("zero" , tlam zeroV)
, ("join" , nlam $ \ parts ->
nlam $ \ each ->
tlam $ \ a -> lam (joinV parts each a))
, ("split" , ecSplitV)
, ("splitAt" , nlam $ \ front ->
nlam $ \ back ->
tlam $ \ a -> lam (splitAtV front back a))
, ("fromThen" , fromThenV)
, ("fromTo" , fromToV)
, ("fromThenTo" , fromThenToV)
, ("infFrom" , nlam $ \(finNat' -> bits) ->
lam $ \(fromWord -> first) ->
toStream (map (word bits) [ first .. ]))
, ("infFromThen", nlam $ \(finNat' -> bits) ->
lam $ \(fromWord -> first) ->
lam $ \(fromWord -> next) ->
toStream [ word bits n | n <- [ first, next .. ] ])
, ("error" , tlam $ \_ ->
tlam $ \_ ->
lam $ \(fromStr -> s) -> cryUserError s)
, ("reverse" , nlam $ \a ->
tlam $ \b ->
lam $ \(fromSeq -> xs) -> toSeq a b (reverse xs))
, ("transpose" , nlam $ \a ->
nlam $ \b ->
tlam $ \c ->
lam $ \((map fromSeq . fromSeq) -> xs) ->
case a of
Nat 0 ->
let val = toSeq a c []
in case b of
Nat n -> toSeq b (tvSeq a c) $ genericReplicate n val
Inf -> VStream $ repeat val
_ -> toSeq b (tvSeq a c) $ map (toSeq a c) $ transpose xs)
, ("pmult" ,
let mul !res !_ !_ 0 = res
mul res bs as n = mul (if even as then res else xor res bs)
(bs `shiftL` 1) (as `shiftR` 1) (n-1)
in nlam $ \(finNat' -> a) ->
nlam $ \(finNat' -> b) ->
lam $ \(fromWord -> x) ->
lam $ \(fromWord -> y) -> word (max 1 (a + b) - 1) (mul 0 x y b))
, ("pdiv" , nlam $ \(fromInteger . finNat' -> a) ->
nlam $ \(fromInteger . finNat' -> b) ->
lam $ \(fromWord -> x) ->
lam $ \(fromWord -> y) -> word (toInteger a)
(fst (divModPoly x a y b)))
, ("pmod" , nlam $ \(fromInteger . finNat' -> a) ->
nlam $ \(fromInteger . finNat' -> b) ->
lam $ \(fromWord -> x) ->
lam $ \(fromWord -> y) -> word (toInteger b)
(snd (divModPoly x a y (b+1))))
, ("random" , tlam $ \a ->
lam $ \(fromWord -> x) -> randomV a x)
]
-- | Make a numeric constant.
ecDemoteV :: Value
ecDemoteV = nlam $ \valT ->
nlam $ \bitT ->
case (valT, bitT) of
(Nat v, Nat bs) -> VWord (mkBv bs v)
_ -> evalPanic "Cryptol.Eval.Prim.evalConst"
["Unexpected Inf in constant."
, show valT
, show bitT
]
--------------------------------------------------------------------------------
divModPoly :: Integer -> Int -> Integer -> Int -> (Integer, Integer)
divModPoly xs xsLen ys ysLen
| ys == 0 = divideByZero
| otherwise = go 0 initR (xsLen - degree) todoBits
where
downIxes n = [ n - 1, n - 2 .. 0 ]
degree = head [ n | n <- downIxes ysLen, testBit ys n ]
initR = xs `shiftR` (xsLen - degree)
nextR r b = (r `shiftL` 1) .|. (if b then 1 else 0)
go !res !r !bitN todo =
let x = xor r ys
(res',r') | testBit x degree = (res, r)
| otherwise = (setBit res bitN, x)
in case todo of
b : bs -> go res' (nextR r' b) (bitN-1) bs
[] -> (res',r')
todoBits = map (testBit xs) (downIxes (xsLen - degree))
-- | Create a packed word
modExp :: Integer -- ^ bit size of the resulting word
-> Integer -- ^ base
-> Integer -- ^ exponent
-> Integer
modExp bits base e
| bits == 0 = 0
| base < 0 || bits < 0 = evalPanic "modExp"
[ "bad args: "
, " base = " ++ show base
, " e = " ++ show e
, " bits = " ++ show modulus
]
| otherwise = doubleAndAdd base e modulus
where
modulus = 0 `setBit` fromInteger bits
doubleAndAdd :: Integer -- ^ base
-> Integer -- ^ exponent mask
-> Integer -- ^ modulus
-> Integer
doubleAndAdd base0 expMask modulus = go 1 base0 expMask
where
go acc base k
| k > 0 = acc' `seq` base' `seq` go acc' base' (k `shiftR` 1)
| otherwise = acc
where
acc' | k `testBit` 0 = acc `modMul` base
| otherwise = acc
base' = base `modMul` base
modMul x y = (x * y) `mod` modulus
-- Operation Lifting -----------------------------------------------------------
type GenBinary b w = TValue -> GenValue b w -> GenValue b w -> GenValue b w
type Binary = GenBinary Bool BV
binary :: GenBinary b w -> GenValue b w
binary f = tlam $ \ ty ->
lam $ \ a ->
lam $ \ b -> f ty a b
type GenUnary b w = TValue -> GenValue b w -> GenValue b w
type Unary = GenUnary Bool BV
unary :: GenUnary b w -> GenValue b w
unary f = tlam $ \ ty ->
lam $ \ a -> f ty a
-- Arith -----------------------------------------------------------------------
-- | Turn a normal binop on Integers into one that can also deal with a bitsize.
liftBinArith :: (Integer -> Integer -> Integer) -> BinArith
liftBinArith op _ = op
type BinArith = Integer -> Integer -> Integer -> Integer
arithBinary :: BinArith -> Binary
arithBinary op = loop
where
loop ty l r = case ty of
-- words and finite sequences
TVSeq w a
| isTBit a -> VWord (mkBv w (op w (fromWord l) (fromWord r)))
| otherwise -> VSeq False (zipWith (loop a) (fromSeq l) (fromSeq r))
-- streams
TVStream a -> toStream (zipWith (loop a) (fromSeq l) (fromSeq r))
-- functions
TVFun _ ety ->
lam $ \ x -> loop ety (fromVFun l x) (fromVFun r x)
-- tuples
TVTuple tys ->
let ls = fromVTuple l
rs = fromVTuple r
in VTuple (zipWith3 loop tys ls rs)
-- records
TVRec fs ->
VRecord [ (f, loop fty (lookupRecord f l) (lookupRecord f r))
| (f,fty) <- fs ]
_ -> evalPanic "arithBinop" ["Invalid arguments"]
arithUnary :: (Integer -> Integer) -> Unary
arithUnary op = loop
where
loop ty x = case ty of
-- words and finite sequences
TVSeq w a
| isTBit a -> VWord (mkBv w (op (fromWord x)))
| otherwise -> VSeq False (map (loop a) (fromSeq x))
-- infinite sequences
TVStream a -> toStream (map (loop a) (fromSeq x))
-- functions
TVFun _ ety ->
lam $ \ y -> loop ety (fromVFun x y)
-- tuples
TVTuple tys ->
let as = fromVTuple x
in VTuple (zipWith loop tys as)
-- records
TVRec fs ->
VRecord [ (f, loop fty (lookupRecord f x)) | (f,fty) <- fs ]
_ -> evalPanic "arithUnary" ["Invalid arguments"]
lg2 :: Integer -> Integer
lg2 i = case genLog i 2 of
Just (i',isExact) | isExact -> i'
| otherwise -> i' + 1
Nothing -> 0
divWrap :: Integral a => a -> a -> a
divWrap _ 0 = divideByZero
divWrap x y = x `div` y
modWrap :: Integral a => a -> a -> a
modWrap _ 0 = divideByZero
modWrap x y = x `mod` y
-- Cmp -------------------------------------------------------------------------
-- | Lexicographic ordering on two values.
lexCompare :: TValue -> Value -> Value -> Ordering
lexCompare ty l r =
case ty of
TVBit -> compare (fromVBit l) (fromVBit r)
TVSeq _ TVBit -> compare (fromWord l) (fromWord r)
TVSeq _ e -> zipLexCompare (repeat e) (fromSeq l) (fromSeq r)
TVTuple etys -> zipLexCompare etys (fromVTuple l) (fromVTuple r)
TVRec fields ->
let tys = map snd (sortBy (comparing fst) fields)
ls = map snd (sortBy (comparing fst) (fromVRecord l))
rs = map snd (sortBy (comparing fst) (fromVRecord r))
in zipLexCompare tys ls rs
_ -> evalPanic "lexCompare" ["invalid type"]
-- XXX the lists are expected to be of the same length, as this should only be
-- used with values that come from type-correct expressions.
zipLexCompare :: [TValue] -> [Value] -> [Value] -> Ordering
zipLexCompare tys ls rs = foldr choose EQ (zipWith3 lexCompare tys ls rs)
where
choose c acc = case c of
EQ -> acc
_ -> c
-- | Process two elements based on their lexicographic ordering.
cmpOrder :: (Ordering -> Bool) -> Binary
cmpOrder op ty l r = VBit (op (lexCompare ty l r))
withOrder :: (Ordering -> TValue -> Value -> Value -> Value) -> Binary
withOrder choose ty l r = choose (lexCompare ty l r) ty l r
maxV :: Ordering -> TValue -> Value -> Value -> Value
maxV o _ l r = case o of
LT -> r
_ -> l
minV :: Ordering -> TValue -> Value -> Value -> Value
minV o _ l r = case o of
GT -> r
_ -> l
funCmp :: (Ordering -> Bool) -> Value
funCmp op =
tlam $ \ _a ->
tlam $ \ b ->
lam $ \ l ->
lam $ \ r ->
lam $ \ x -> cmpOrder op b (fromVFun l x) (fromVFun r x)
-- Logic -----------------------------------------------------------------------
zeroV :: TValue -> Value
zeroV ty = case ty of
-- bits
TVBit ->
VBit False
-- finite sequences
TVSeq w ety
| isTBit ety -> word w 0
| otherwise -> toFinSeq ety (replicate (fromInteger w) (zeroV ety))
-- infinite sequences
TVStream ety -> toStream (repeat (zeroV ety))
-- functions
TVFun _ bty ->
lam (\ _ -> zeroV bty)
-- tuples
TVTuple tys ->
VTuple (map zeroV tys)
-- records
TVRec fields ->
VRecord [ (f,zeroV fty) | (f,fty) <- fields ]
-- | Join a sequence of sequences into a single sequence.
joinV :: Nat' -> Nat' -> TValue -> Value -> Value
joinV parts each a val =
let len = parts `nMul` each
in toSeq len a (concatMap fromSeq (fromSeq val))
splitAtV :: Nat' -> Nat' -> TValue -> Value -> Value
splitAtV front back a val =
case back of
-- Remember that words are big-endian in cryptol, so the first component
-- needs to be shifted, and the second component just needs to be masked.
Nat rightWidth | aBit, VWord (BV _ i) <- val ->
VTuple [ VWord (BV leftWidth (i `shiftR` fromInteger rightWidth))
, VWord (mkBv rightWidth i) ]
_ ->
let (ls,rs) = genericSplitAt leftWidth (fromSeq val)
in VTuple [VSeq aBit ls, toSeq back a rs]
where
aBit = isTBit a
leftWidth = case front of
Nat n -> n
_ -> evalPanic "splitAtV" ["invalid `front` len"]
-- | Split implementation.
ecSplitV :: Value
ecSplitV =
nlam $ \ parts ->
nlam $ \ each ->
tlam $ \ a ->
lam $ \ val ->
let mkChunks f = map (toFinSeq a) $ f $ fromSeq val
in case (parts, each) of
(Nat p, Nat e) -> VSeq False $ mkChunks (finChunksOf p e)
(Inf , Nat e) -> toStream $ mkChunks (infChunksOf e)
_ -> evalPanic "splitV" ["invalid type arguments to split"]
-- | Split into infinitely many chunks
infChunksOf :: Integer -> [a] -> [[a]]
infChunksOf each xs = let (as,bs) = genericSplitAt each xs
in as : infChunksOf each bs
-- | Split into finitely many chunks
finChunksOf :: Integer -> Integer -> [a] -> [[a]]
finChunksOf 0 _ _ = []
finChunksOf parts each xs = let (as,bs) = genericSplitAt each xs
in as : finChunksOf (parts - 1) each bs
ccatV :: Nat' -> Nat' -> TValue -> Value -> Value -> Value
ccatV _front _back (isTBit -> True) (VWord (BV i x)) (VWord (BV j y)) =
VWord (BV (i + j) (shiftL x (fromInteger j) + y))
ccatV front back elty l r =
toSeq (evalTF TCAdd [front,back]) elty (fromSeq l ++ fromSeq r)
-- | Merge two values given a binop. This is used for and, or and xor.
logicBinary :: (forall a. Bits a => a -> a -> a) -> Binary
logicBinary op = loop
where
loop ty l r = case ty of
TVBit -> VBit (op (fromVBit l) (fromVBit r))
-- words or finite sequences
TVSeq w aty
| isTBit aty -> VWord (BV w (op (fromWord l) (fromWord r)))
-- We assume that bitwise ops do not need re-masking
| otherwise -> VSeq False (zipWith (loop aty) (fromSeq l)
(fromSeq r))
-- streams
TVStream aty -> toStream (zipWith (loop aty) (fromSeq l) (fromSeq r))
TVTuple etys ->
let ls = fromVTuple l
rs = fromVTuple r
in VTuple (zipWith3 loop etys ls rs)
TVFun _ bty ->
lam $ \ a -> loop bty (fromVFun l a) (fromVFun r a)
TVRec fields ->
VRecord [ (f,loop fty a b) | (f,fty) <- fields
, let a = lookupRecord f l
b = lookupRecord f r
]
logicUnary :: (forall a. Bits a => a -> a) -> Unary
logicUnary op = loop
where
loop ty val = case ty of
TVBit -> VBit (op (fromVBit val))
-- words or finite sequences
TVSeq w ety
| isTBit ety -> VWord (mkBv w (op (fromWord val)))
| otherwise -> VSeq False (map (loop ety) (fromSeq val))
-- streams
TVStream ety -> toStream (map (loop ety) (fromSeq val))
TVTuple etys ->
let as = fromVTuple val
in VTuple (zipWith loop etys as)
TVFun _ bty ->
lam $ \ a -> loop bty (fromVFun val a)
TVRec fields ->
VRecord [ (f,loop fty a) | (f,fty) <- fields, let a = lookupRecord f val ]
logicShift :: (Integer -> Integer -> Integer -> Integer)
-- ^ The function may assume its arguments are masked.
-- It is responsible for masking its result if needed.
-> (Nat' -> TValue -> [Value] -> Integer -> [Value])
-> Value
logicShift opW opS
= nlam $ \ a ->
tlam $ \ _ ->
tlam $ \ c ->
lam $ \ l ->
lam $ \ r ->
if isTBit c
then -- words
let BV w i = fromVWord l
in VWord (BV w (opW w i (fromWord r)))
else toSeq a c (opS a c (fromSeq l) (fromWord r))
-- Left shift for words.
shiftLW :: Integer -> Integer -> Integer -> Integer
shiftLW w ival by
| by >= w = 0
| otherwise = mask w (shiftL ival (fromInteger by))
shiftLS :: Nat' -> TValue -> [Value] -> Integer -> [Value]
shiftLS w ety vs by =
case w of
Nat len
| by < len -> genericTake len (genericDrop by vs ++ repeat (zeroV ety))
| otherwise -> genericReplicate len (zeroV ety)
Inf -> genericDrop by vs
shiftRW :: Integer -> Integer -> Integer -> Integer
shiftRW w i by
| by >= w = 0
| otherwise = shiftR i (fromInteger by)
shiftRS :: Nat' -> TValue -> [Value] -> Integer -> [Value]
shiftRS w ety vs by =
case w of
Nat len
| by < len -> genericTake len (genericReplicate by (zeroV ety) ++ vs)
| otherwise -> genericReplicate len (zeroV ety)
Inf -> genericReplicate by (zeroV ety) ++ vs
-- XXX integer doesn't implement rotateL, as there's no bit bound
rotateLW :: Integer -> Integer -> Integer -> Integer
rotateLW 0 i _ = i
rotateLW w i by = mask w $ (i `shiftL` b) .|. (i `shiftR` (fromInteger w - b))
where b = fromInteger (by `mod` w)
rotateLS :: Nat' -> TValue -> [Value] -> Integer -> [Value]
rotateLS w _ vs at =
case w of
Nat len -> let at' = at `mod` len
(ls,rs) = genericSplitAt at' vs
in rs ++ ls
_ -> panic "Cryptol.Eval.Prim.rotateLS" [ "unexpected infinite sequence" ]
-- XXX integer doesn't implement rotateR, as there's no bit bound
rotateRW :: Integer -> Integer -> Integer -> Integer
rotateRW 0 i _ = i
rotateRW w i by = mask w $ (i `shiftR` b) .|. (i `shiftL` (fromInteger w - b))
where b = fromInteger (by `mod` w)
rotateRS :: Nat' -> TValue -> [Value] -> Integer -> [Value]
rotateRS w _ vs at =
case w of
Nat len -> let at' = at `mod` len
(ls,rs) = genericSplitAt (len - at') vs
in rs ++ ls
_ -> panic "Cryptol.Eval.Prim.rotateRS" [ "unexpected infinite sequence" ]
-- Sequence Primitives ---------------------------------------------------------
-- | Indexing operations that return one element.
indexPrimOne :: (Maybe Integer -> [Value] -> Integer -> Value) -> Value
indexPrimOne op =
nlam $ \ n ->
tlam $ \ _a ->
nlam $ \ _i ->
lam $ \ l ->
lam $ \ r ->
let vs = fromSeq l
ix = fromWord r
in op (fromNat n) vs ix
indexFront :: Maybe Integer -> [Value] -> Integer -> Value
indexFront mblen vs ix =
case mblen of
Just len | len <= ix -> invalidIndex ix
_ -> genericIndex vs ix
indexBack :: Maybe Integer -> [Value] -> Integer -> Value
indexBack mblen vs ix =
case mblen of
Just len | len > ix -> genericIndex vs (len - ix - 1)
| otherwise -> invalidIndex ix
Nothing -> evalPanic "indexBack"
["unexpected infinite sequence"]
-- | Indexing operations that return many elements.
indexPrimMany :: (Maybe Integer -> [Value] -> [Integer] -> [Value]) -> Value
indexPrimMany op =
nlam $ \ n ->
tlam $ \ a ->
nlam $ \ m ->
tlam $ \ _i ->
lam $ \ l ->
lam $ \ r ->
let vs = fromSeq l
ixs = map fromWord (fromSeq r)
in toSeq m a (op (fromNat (n)) vs ixs)
indexFrontRange :: Maybe Integer -> [Value] -> [Integer] -> [Value]
indexFrontRange mblen vs = map (indexFront mblen vs)
indexBackRange :: Maybe Integer -> [Value] -> [Integer] -> [Value]
indexBackRange mblen vs = map (indexBack mblen vs)
-- @[ 0, 1 .. ]@
fromThenV :: Value
fromThenV =
nlam $ \ first ->
nlam $ \ next ->
nlam $ \ bits ->
nlam $ \ len ->
case (first, next, len, bits) of
(_ , _ , _ , Nat bits')
| bits' >= Arch.maxBigIntWidth -> wordTooWide bits'
(Nat first', Nat next', Nat len', Nat bits') ->
let nums = enumFromThen first' next'
in VSeq False (genericTake len' (map (VWord . BV bits') nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- @[ 0 .. 10 ]@
fromToV :: Value
fromToV =
nlam $ \ first ->
nlam $ \ lst ->
nlam $ \ bits ->
case (first, lst, bits) of
(_ , _ , Nat bits')
| bits' >= Arch.maxBigIntWidth -> wordTooWide bits'
(Nat first', Nat lst', Nat bits') ->
let nums = enumFromThenTo first' (first' + 1) lst'
len = 1 + (lst' - first')
in VSeq False (genericTake len (map (VWord . BV bits') nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- @[ 0, 1 .. 10 ]@
fromThenToV :: Value
fromThenToV =
nlam $ \ first ->
nlam $ \ next ->
nlam $ \ lst ->
nlam $ \ bits ->
nlam $ \ len ->
case (first, next, lst, len, bits) of
(_ , _ , _ , _ , Nat bits')
| bits' >= Arch.maxBigIntWidth -> wordTooWide bits'
(Nat first', Nat next', Nat lst', Nat len', Nat bits') ->
let nums = enumFromThenTo first' next' lst'
in VSeq False (genericTake len' (map (VWord . BV bits') nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- Random Values ---------------------------------------------------------------
-- | Produce a random value with the given seed. If we do not support
-- making values of the given type, return zero of that type.
-- TODO: do better than returning zero
randomV :: TValue -> Integer -> Value
randomV ty seed =
case randomValue (tValTy ty) of
Nothing -> zeroV ty
Just gen ->
-- unpack the seed into four Word64s
let mask64 = 0xFFFFFFFFFFFFFFFF
unpack s = fromIntegral (s .&. mask64) : unpack (s `shiftR` 64)
[a, b, c, d] = take 4 (unpack seed)
in fst $ gen 100 $ seedTFGen (a, b, c, d)
cryptol-2.4.0/src/Cryptol/Prims/Syntax.hs 0000644 0000000 0000000 00000006672 12737220176 016560 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.Prims.Syntax
( TFun(..), tBinOpPrec, tfunNames
) where
import Cryptol.Parser.Name (PName,mkUnqual)
import Cryptol.Utils.Ident (packIdent,packInfix)
import Cryptol.Utils.PP
import qualified Data.Map as Map
import GHC.Generics (Generic)
import Control.DeepSeq
-- | Built-in types.
data TFun
= TCAdd -- ^ @ : Num -> Num -> Num @
| TCSub -- ^ @ : Num -> Num -> Num @
| TCMul -- ^ @ : Num -> Num -> Num @
| TCDiv -- ^ @ : Num -> Num -> Num @
| TCMod -- ^ @ : Num -> Num -> Num @
| TCExp -- ^ @ : Num -> Num -> Num @
| TCWidth -- ^ @ : Num -> Num @
| TCMin -- ^ @ : Num -> Num -> Num @
| TCMax -- ^ @ : Num -> Num -> Num @
-- Computing the lengths of explicit enumerations
| TCLenFromThen -- ^ @ : Num -> Num -> Num -> Num@
-- Example: @[ 1, 5 .. ] :: [lengthFromThen 1 5 b][b]@
| TCLenFromThenTo -- ^ @ : Num -> Num -> Num -> Num@
-- Example: @[ 1, 5 .. 9 ] :: [lengthFromThenTo 1 5 9][b]@
deriving (Show, Eq, Ord, Bounded, Enum, Generic, NFData)
tBinOpPrec :: Map.Map TFun (Assoc,Int)
tBinOpPrec = mkMap t_table
where
mkMap t = Map.fromList [ (op,(a,n)) | ((a,ops),n) <- zip t [1..] , op <- ops ]
-- lowest to highest
t_table =
[ (LeftAssoc, [ TCAdd, TCSub ])
, (LeftAssoc, [ TCMul, TCDiv, TCMod ])
, (RightAssoc, [ TCExp ])
]
-- | Type functions, with their arity and function constructor.
tfunNames :: Map.Map PName (Int,TFun)
tfunNames = Map.fromList
[ tinfix "+" 2 TCAdd
, tinfix "-" 2 TCSub
, tinfix "*" 2 TCMul
, tinfix "/" 2 TCDiv
, tinfix "%" 2 TCMod
, tinfix "^^" 2 TCExp
, tprefix "width" 1 TCWidth
, tprefix "min" 2 TCMin
, tprefix "max" 2 TCMax
, tprefix "lengthFromThen" 3 TCLenFromThen
, tprefix "lengthFromThenTo" 3 TCLenFromThenTo
]
where
tprefix n a p = (mkUnqual (packIdent n), (a,p))
tinfix n a p = (mkUnqual (packInfix n), (a,p))
instance PPName TFun where
ppNameFixity f = Map.lookup f tBinOpPrec
ppPrefixName TCAdd = text "(+)"
ppPrefixName TCSub = text "(-)"
ppPrefixName TCMul = text "(*)"
ppPrefixName TCDiv = text "(/)"
ppPrefixName TCMod = text "(%)"
ppPrefixName TCExp = text "(^^)"
ppPrefixName f = pp f
ppInfixName TCAdd = text "+"
ppInfixName TCSub = text "-"
ppInfixName TCMul = text "*"
ppInfixName TCDiv = text "/"
ppInfixName TCMod = text "%"
ppInfixName TCExp = text "^^"
ppInfixName f = error $ "Not a prefix type function: " ++ show (pp f)
instance PP TFun where
ppPrec _ tcon =
case tcon of
TCAdd -> text "+"
TCSub -> text "-"
TCMul -> text "*"
TCDiv -> text "/"
TCMod -> text "%"
TCExp -> text "^^"
TCWidth -> text "width"
TCMin -> text "min"
TCMax -> text "max"
TCLenFromThen -> text "lengthFromThen"
TCLenFromThenTo -> text "lengthFromThenTo"
cryptol-2.4.0/src/Cryptol/REPL/ 0000755 0000000 0000000 00000000000 12737220176 014373 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/REPL/Command.hs 0000644 0000000 0000000 00000110165 12737220176 016311 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
module Cryptol.REPL.Command (
-- * Commands
Command(..), CommandDescr(..), CommandBody(..)
, parseCommand
, runCommand
, splitCommand
, findCommand
, findCommandExact
, findNbCommand
, moduleCmd, loadCmd, loadPrelude, setOptionCmd
-- Parsing
, interactiveConfig
, replParseExpr
-- Evaluation and Typechecking
, replEvalExpr
, replCheckExpr
-- Check, SAT, and prove
, qcCmd, QCMode(..)
, satCmd
, proveCmd
, onlineProveSat
, offlineProveSat
-- Misc utilities
, handleCtrlC
, sanitize
-- To support Notebook interface (might need to refactor)
, replParse
, liftModuleCmd
, moduleCmdResult
) where
import Cryptol.REPL.Monad
import Cryptol.REPL.Trie
import qualified Cryptol.ModuleSystem as M
import qualified Cryptol.ModuleSystem.Name as M
import qualified Cryptol.ModuleSystem.NamingEnv as M
import qualified Cryptol.ModuleSystem.Renamer as M (RenamerWarning(SymbolShadowed))
import qualified Cryptol.Utils.Ident as M
import qualified Cryptol.Eval.Value as E
import Cryptol.Testing.Concrete
import qualified Cryptol.Testing.Random as TestR
import Cryptol.Parser
(parseExprWith,parseReplWith,ParseError(),Config(..),defaultConfig
,parseModName,parseHelpName)
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck.Subst as T
import qualified Cryptol.TypeCheck.InferTypes as T
import Cryptol.TypeCheck.Solve(defaultReplExpr)
import qualified Cryptol.TypeCheck.Solver.CrySAT as CrySAT
import Cryptol.TypeCheck.PP (dump,ppWithNames)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic(panic)
import qualified Cryptol.Parser.AST as P
import qualified Cryptol.Transform.Specialize as S
import Cryptol.Symbolic (ProverCommand(..), QueryType(..), SatNum(..))
import qualified Cryptol.Symbolic as Symbolic
import Control.DeepSeq
import qualified Control.Exception as X
import Control.Monad hiding (mapM, mapM_)
import qualified Data.ByteString as BS
import Data.Bits ((.&.))
import Data.Char (isSpace,isPunctuation,isSymbol)
import Data.Function (on)
import Data.List (intercalate,nub,sortBy,partition)
import Data.Maybe (fromMaybe,mapMaybe)
import System.Environment (lookupEnv)
import System.Exit (ExitCode(ExitSuccess))
import System.Process (shell,createProcess,waitForProcess)
import qualified System.Process as Process(runCommand)
import System.FilePath((>), isPathSeparator)
import System.Directory(getHomeDirectory,setCurrentDirectory,doesDirectoryExist)
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.IntMap as IntMap
import System.IO(hFlush,stdout)
import System.Random.TF(newTFGen)
import Numeric (showFFloat)
import qualified Data.Text as ST
import qualified Data.Text.Lazy as T
import Prelude ()
import Prelude.Compat
-- Commands --------------------------------------------------------------------
-- | Commands.
data Command
= Command (REPL ()) -- ^ Successfully parsed command
| Ambiguous String [String] -- ^ Ambiguous command, list of conflicting
-- commands
| Unknown String -- ^ The unknown command
-- | Command builder.
data CommandDescr = CommandDescr
{ cNames :: [String]
, cBody :: CommandBody
, cHelp :: String
}
instance Show CommandDescr where
show = show . cNames
instance Eq CommandDescr where
(==) = (==) `on` cNames
instance Ord CommandDescr where
compare = compare `on` cNames
data CommandBody
= ExprArg (String -> REPL ())
| FileExprArg (FilePath -> String -> REPL ())
| DeclsArg (String -> REPL ())
| ExprTypeArg (String -> REPL ())
| FilenameArg (FilePath -> REPL ())
| OptionArg (String -> REPL ())
| ShellArg (String -> REPL ())
| NoArg (REPL ())
-- | REPL command parsing.
commands :: CommandMap
commands = foldl insert emptyTrie commandList
where
insert m d = foldl (insertOne d) m (cNames d)
insertOne d m name = insertTrie name d m
-- | Notebook command parsing.
nbCommands :: CommandMap
nbCommands = foldl insert emptyTrie nbCommandList
where
insert m d = foldl (insertOne d) m (cNames d)
insertOne d m name = insertTrie name d m
-- | A subset of commands safe for Notebook execution
nbCommandList :: [CommandDescr]
nbCommandList =
[ CommandDescr [ ":t", ":type" ] (ExprArg typeOfCmd)
"check the type of an expression"
, CommandDescr [ ":b", ":browse" ] (ExprTypeArg browseCmd)
"display the current environment"
, CommandDescr [ ":?", ":help" ] (ExprArg helpCmd)
"display a brief description about a function"
, CommandDescr [ ":s", ":set" ] (OptionArg setOptionCmd)
"set an environmental option (:set on its own displays current values)"
, CommandDescr [ ":check" ] (ExprArg (void . qcCmd QCRandom))
"use random testing to check that the argument always returns true (if no argument, check all properties)"
, CommandDescr [ ":exhaust" ] (ExprArg (void . qcCmd QCExhaust))
"use exhaustive testing to prove that the argument always returns true (if no argument, check all properties)"
, CommandDescr [ ":prove" ] (ExprArg proveCmd)
"use an external solver to prove that the argument always returns true (if no argument, check all properties)"
, CommandDescr [ ":sat" ] (ExprArg satCmd)
"use a solver to find a satisfying assignment for which the argument returns true (if no argument, find an assignment for all properties)"
, CommandDescr [ ":debug_specialize" ] (ExprArg specializeCmd)
"do type specialization on a closed expression"
]
commandList :: [CommandDescr]
commandList =
nbCommandList ++
[ CommandDescr [ ":q", ":quit" ] (NoArg quitCmd)
"exit the REPL"
, CommandDescr [ ":l", ":load" ] (FilenameArg loadCmd)
"load a module"
, CommandDescr [ ":r", ":reload" ] (NoArg reloadCmd)
"reload the currently loaded module"
, CommandDescr [ ":e", ":edit" ] (FilenameArg editCmd)
"edit the currently loaded module"
, CommandDescr [ ":!" ] (ShellArg runShellCmd)
"execute a command in the shell"
, CommandDescr [ ":cd" ] (FilenameArg cdCmd)
"set the current working directory"
, CommandDescr [ ":m", ":module" ] (FilenameArg moduleCmd)
"load a module"
, CommandDescr [ ":w", ":writeByteArray" ] (FileExprArg writeFileCmd)
"write data of type `fin n => [n][8]` to a file"
, CommandDescr [ ":readByteArray" ] (FilenameArg readFileCmd)
"read data from a file as type `fin n => [n][8]`, binding the value to variable `it`"
]
genHelp :: [CommandDescr] -> [String]
genHelp cs = map cmdHelp cs
where
cmdHelp cmd = concat [ " ", cmdNames cmd, pad (cmdNames cmd), cHelp cmd ]
cmdNames cmd = intercalate ", " (cNames cmd)
padding = 2 + maximum (map (length . cmdNames) cs)
pad n = replicate (max 0 (padding - length n)) ' '
-- Command Evaluation ----------------------------------------------------------
-- | Run a command.
runCommand :: Command -> REPL ()
runCommand c = case c of
Command cmd -> cmd `Cryptol.REPL.Monad.catch` handler
where
handler re = rPutStrLn "" >> rPrint (pp re)
Unknown cmd -> rPutStrLn ("Unknown command: " ++ cmd)
Ambiguous cmd cmds -> do
rPutStrLn (cmd ++ " is ambiguous, it could mean one of:")
rPutStrLn ("\t" ++ intercalate ", " cmds)
-- Get the setting we should use for displaying values.
getPPValOpts :: REPL E.PPOpts
getPPValOpts =
do EnvNum base <- getUser "base"
EnvBool ascii <- getUser "ascii"
EnvNum infLength <- getUser "infLength"
return E.PPOpts { E.useBase = base
, E.useAscii = ascii
, E.useInfLength = infLength
}
evalCmd :: String -> REPL ()
evalCmd str = do
letEnabled <- getLetEnabled
ri <- if letEnabled
then replParseInput str
else P.ExprInput <$> replParseExpr str
case ri of
P.ExprInput expr -> do
(val,_ty) <- replEvalExpr expr
ppOpts <- getPPValOpts
-- This is the point where the value gets forced. We deepseq the
-- pretty-printed representation of it, rather than the value
-- itself, leaving it up to the pretty-printer to determine how
-- much of the value to force
out <- io $ rethrowEvalError
$ return $!! show $ pp $ E.WithBase ppOpts val
rPutStrLn out
P.LetInput decl -> do
-- explicitly make this a top-level declaration, so that it will
-- be generalized if mono-binds is enabled
replEvalDecl decl
data QCMode = QCRandom | QCExhaust deriving (Eq, Show)
-- | Randomly test a property, or exhaustively check it if the number
-- of values in the type under test is smaller than the @tests@
-- environment variable, or we specify exhaustive testing.
qcCmd :: QCMode -> String -> REPL [TestReport]
qcCmd qcMode "" =
do (xs,disp) <- getPropertyNames
let nameStr x = show (fixNameDisp disp (pp x))
if null xs
then rPutStrLn "There are no properties in scope." *> return []
else concat <$> (forM xs $ \x ->
do let str = nameStr x
rPutStr $ "property " ++ str ++ " "
qcCmd qcMode str)
qcCmd qcMode str =
do expr <- replParseExpr str
(val,ty) <- replEvalExpr expr
EnvNum testNum <- getUser "tests"
case testableType ty of
Just (sz,vss) | qcMode == QCExhaust || sz <= toInteger testNum -> do
rPutStrLn "Using exhaustive testing."
let f _ [] = panic "Cryptol.REPL.Command"
["Exhaustive testing ran out of test cases"]
f _ (vs : vss1) = do
result <- io $ runOneTest val vs
return (result, vss1)
testSpec = TestSpec {
testFn = f
, testProp = str
, testTotal = sz
, testPossible = sz
, testRptProgress = ppProgress
, testClrProgress = delProgress
, testRptFailure = ppFailure
, testRptSuccess = do
delTesting
prtLn $ "passed " ++ show sz ++ " tests."
rPutStrLn "Q.E.D."
}
prt testingMsg
report <- runTests testSpec vss
return [report]
Just (sz,_) -> case TestR.testableType ty of
Nothing -> raise (TypeNotTestable ty)
Just gens -> do
rPutStrLn "Using random testing."
let testSpec = TestSpec {
testFn = \sz' g -> io $ TestR.runOneTest val gens sz' g
, testProp = str
, testTotal = toInteger testNum
, testPossible = sz
, testRptProgress = ppProgress
, testClrProgress = delProgress
, testRptFailure = ppFailure
, testRptSuccess = do
delTesting
prtLn $ "passed " ++ show testNum ++ " tests."
}
prt testingMsg
g <- io newTFGen
report <- runTests testSpec g
when (isPass (reportResult report)) $ do
let szD = fromIntegral sz :: Double
percent = fromIntegral (testNum * 100) / szD
showValNum
| sz > 2 ^ (20::Integer) =
"2^^" ++ show (lg2 sz)
| otherwise = show sz
rPutStrLn $ "Coverage: "
++ showFFloat (Just 2) percent "% ("
++ show testNum ++ " of "
++ showValNum ++ " values)"
return [report]
Nothing -> return []
where
testingMsg = "testing..."
totProgressWidth = 4 -- 100%
lg2 :: Integer -> Integer
lg2 x | x >= 2^(1024::Int) = 1024 + lg2 (x `div` 2^(1024::Int))
| x == 0 = 0
| otherwise = let valNumD = fromIntegral x :: Double
in round $ logBase 2 valNumD :: Integer
prt msg = rPutStr msg >> io (hFlush stdout)
prtLn msg = rPutStrLn msg >> io (hFlush stdout)
ppProgress this tot = unlessBatch $
let percent = show (div (100 * this) tot) ++ "%"
width = length percent
pad = replicate (totProgressWidth - width) ' '
in prt (pad ++ percent)
del n = unlessBatch $ prt (replicate n '\BS')
delTesting = del (length testingMsg)
delProgress = del totProgressWidth
ppFailure failure = do
delTesting
opts <- getPPValOpts
case failure of
FailFalse [] -> do
prtLn "FAILED"
FailFalse vs -> do
prtLn "FAILED for the following inputs:"
mapM_ (rPrint . pp . E.WithBase opts) vs
FailError err [] -> do
prtLn "ERROR"
rPrint (pp err)
FailError err vs -> do
prtLn "ERROR for the following inputs:"
mapM_ (rPrint . pp . E.WithBase opts) vs
rPrint (pp err)
Pass -> panic "Cryptol.REPL.Command" ["unexpected Test.Pass"]
satCmd, proveCmd :: String -> REPL ()
satCmd = cmdProveSat True
proveCmd = cmdProveSat False
-- | Console-specific version of 'proveSat'. Prints output to the
-- console, and binds the @it@ variable to a record whose form depends
-- on the expression given. See ticket #66 for a discussion of this
-- design.
cmdProveSat :: Bool -> String -> REPL ()
cmdProveSat isSat "" =
do (xs,disp) <- getPropertyNames
let nameStr x = show (fixNameDisp disp (pp x))
if null xs
then rPutStrLn "There are no properties in scope."
else forM_ xs $ \x ->
do let str = nameStr x
if isSat
then rPutStr $ ":sat " ++ str ++ "\n\t"
else rPutStr $ ":prove " ++ str ++ "\n\t"
cmdProveSat isSat str
cmdProveSat isSat str = do
let cexStr | isSat = "satisfying assignment"
| otherwise = "counterexample"
EnvString proverName <- getUser "prover"
EnvString fileName <- getUser "smtfile"
let mfile = if fileName == "-" then Nothing else Just fileName
case proverName of
"offline" -> do
result <- offlineProveSat isSat str mfile
case result of
Left msg -> rPutStrLn msg
Right smtlib -> do
let filename = fromMaybe "standard output" mfile
let satWord | isSat = "satisfiability"
| otherwise = "validity"
rPutStrLn $
"Writing to SMT-Lib file " ++ filename ++ "..."
rPutStrLn $
"To determine the " ++ satWord ++
" of the expression, use an external SMT solver."
case mfile of
Just path -> io $ writeFile path smtlib
Nothing -> rPutStr smtlib
_ -> do
result <- onlineProveSat isSat str mfile
ppOpts <- getPPValOpts
case result of
Symbolic.EmptyResult ->
panic "REPL.Command" [ "got EmptyResult for online prover query" ]
Symbolic.ProverError msg -> rPutStrLn msg
Symbolic.ThmResult ts -> do
rPutStrLn (if isSat then "Unsatisfiable" else "Q.E.D.")
(t, e) <- mkSolverResult cexStr (not isSat) (Left ts)
bindItVariable t e
Symbolic.AllSatResult tevss -> do
let tess = map (map $ \(t,e,_) -> (t,e)) tevss
vss = map (map $ \(_,_,v) -> v) tevss
ppvs vs = do
parseExpr <- replParseExpr str
let docs = map (pp . E.WithBase ppOpts) vs
-- function application has precedence 3
doc = ppPrec 3 parseExpr
rPrint $ hang doc 2 (sep docs) <+>
text (if isSat then "= True" else "= False")
resultRecs <- mapM (mkSolverResult cexStr isSat . Right) tess
let collectTes tes = (t, es)
where
(ts, es) = unzip tes
t = case nub ts of
[t'] -> t'
_ -> panic "REPL.Command.onlineProveSat"
[ "satisfying assignments with different types" ]
(ty, exprs) =
case resultRecs of
[] -> panic "REPL.Command.onlineProveSat"
[ "no satisfying assignments after mkSovlerResult" ]
[(t, e)] -> (t, [e])
_ -> collectTes resultRecs
forM_ vss ppvs
case (ty, exprs) of
(t, [e]) -> bindItVariable t e
(t, es ) -> bindItVariables t es
onlineProveSat :: Bool
-> String -> Maybe FilePath -> REPL Symbolic.ProverResult
onlineProveSat isSat str mfile = do
EnvString proverName <- getUser "prover"
EnvBool verbose <- getUser "debug"
satNum <- getUserSatNum
parseExpr <- replParseExpr str
(_, expr, schema) <- replCheckExpr parseExpr
decls <- fmap M.deDecls getDynEnv
let cmd = Symbolic.ProverCommand {
pcQueryType = if isSat then SatQuery satNum else ProveQuery
, pcProverName = proverName
, pcVerbose = verbose
, pcExtraDecls = decls
, pcSmtFile = mfile
, pcExpr = expr
, pcSchema = schema
}
liftModuleCmd $ Symbolic.satProve cmd
offlineProveSat :: Bool -> String -> Maybe FilePath -> REPL (Either String String)
offlineProveSat isSat str mfile = do
EnvBool verbose <- getUser "debug"
parseExpr <- replParseExpr str
(_, expr, schema) <- replCheckExpr parseExpr
decls <- fmap M.deDecls getDynEnv
let cmd = Symbolic.ProverCommand {
pcQueryType = if isSat then SatQuery (SomeSat 0) else ProveQuery
, pcProverName = "offline"
, pcVerbose = verbose
, pcExtraDecls = decls
, pcSmtFile = mfile
, pcExpr = expr
, pcSchema = schema
}
liftModuleCmd $ Symbolic.satProveOffline cmd
rIdent :: M.Ident
rIdent = M.packIdent "result"
-- | Make a type/expression pair that is suitable for binding to @it@
-- after running @:sat@ or @:prove@
mkSolverResult :: String
-> Bool
-> Either [T.Type] [(T.Type, T.Expr)]
-> REPL (T.Type, T.Expr)
mkSolverResult thing result earg =
do prims <- getPrimMap
let addError t = (t, T.eError prims t ("no " ++ thing ++ " available"))
argF = case earg of
Left ts -> mkArgs (map addError ts)
Right tes -> mkArgs tes
eTrue = T.ePrim prims (M.packIdent "True")
eFalse = T.ePrim prims (M.packIdent "False")
resultE = if result then eTrue else eFalse
rty = T.TRec $ [(rIdent, T.tBit )] ++ map fst argF
re = T.ERec $ [(rIdent, resultE)] ++ map snd argF
return (rty, re)
where
mkArgs tes = zipWith mkArg [1 :: Int ..] tes
where
mkArg n (t,e) =
let argName = M.packIdent ("arg" ++ show n)
in ((argName,t),(argName,e))
specializeCmd :: String -> REPL ()
specializeCmd str = do
parseExpr <- replParseExpr str
(_, expr, schema) <- replCheckExpr parseExpr
spexpr <- replSpecExpr expr
rPutStrLn "Expression type:"
rPrint $ pp schema
rPutStrLn "Original expression:"
rPutStrLn $ dump expr
rPutStrLn "Specialized expression:"
rPutStrLn $ dump spexpr
typeOfCmd :: String -> REPL ()
typeOfCmd str = do
expr <- replParseExpr str
(_re,def,sig) <- replCheckExpr expr
-- XXX need more warnings from the module system
--io (mapM_ printWarning ws)
whenDebug (rPutStrLn (dump def))
(_,_,names) <- getFocusedEnv
-- type annotation ':' has precedence 2
rPrint $ runDoc names $ ppPrec 2 expr <+> text ":" <+> pp sig
readFileCmd :: FilePath -> REPL ()
readFileCmd fp = do
bytes <- replReadFile fp (\err -> rPutStrLn (show err) >> return Nothing)
case bytes of
Nothing -> return ()
Just bs ->
do pm <- getPrimMap
let expr = T.eString pm (map (toEnum . fromIntegral) (BS.unpack bs))
ty = T.tString (BS.length bs)
bindItVariable ty expr
writeFileCmd :: FilePath -> String -> REPL ()
writeFileCmd file str = do
expr <- replParseExpr str
(val,ty) <- replEvalExpr expr
if not (tIsByteSeq ty)
then rPrint $ "Cannot write expression of types other than [n][8]."
<+> "Type was: " <+> pp ty
else wf file =<< serializeValue val
where
wf fp bytes = replWriteFile fp bytes (rPutStrLn . show)
tIsByteSeq x = maybe False
(tIsByte . snd)
(T.tIsSeq x)
tIsByte x = maybe False
(\(n,b) -> T.tIsBit b && T.tIsNum n == Just 8)
(T.tIsSeq x)
serializeValue (E.VSeq _ vs) =
return $ BS.pack $ map (serializeByte . E.fromVWord) vs
serializeValue _ =
panic "Cryptol.REPL.Command.writeFileCmd"
["Impossible: Non-VSeq value of type [n][8]."]
serializeByte (E.BV _ v) = fromIntegral (v .&. 0xFF)
reloadCmd :: REPL ()
reloadCmd = do
mb <- getLoadedMod
case mb of
Just m -> loadCmd (lPath m)
Nothing -> return ()
editCmd :: String -> REPL ()
editCmd path
| null path = do
mb <- getLoadedMod
case mb of
Just m -> do
success <- replEdit (lPath m)
if success
then loadCmd (lPath m)
else return ()
Nothing -> do
rPutStrLn "No files to edit."
return ()
| otherwise = do
_ <- replEdit path
mb <- getLoadedMod
case mb of
Nothing -> loadCmd path
Just _ -> return ()
moduleCmd :: String -> REPL ()
moduleCmd modString
| null modString = return ()
| otherwise = do
case parseModName modString of
Just m -> loadCmd =<< liftModuleCmd (M.findModule m)
Nothing -> rPutStrLn "Invalid module name."
loadPrelude :: REPL ()
loadPrelude = moduleCmd $ show $ pp M.preludeName
loadCmd :: FilePath -> REPL ()
loadCmd path
| null path = return ()
| otherwise = do
setLoadedMod LoadedModule
{ lName = Nothing
, lPath = path
}
m <- liftModuleCmd (M.loadModuleByPath path)
whenDebug (rPutStrLn (dump m))
setLoadedMod LoadedModule
{ lName = Just (T.mName m)
, lPath = path
}
setDynEnv mempty
quitCmd :: REPL ()
quitCmd = stop
browseCmd :: String -> REPL ()
browseCmd pfx = do
(iface,names,disp) <- getFocusedEnv
let (visibleTypes,visibleDecls) = M.visibleNames names
(visibleType,visibleDecl)
| null pfx =
((`Set.member` visibleTypes)
,(`Set.member` visibleDecls))
| otherwise =
(\n -> n `Set.member` visibleTypes && pfx `isNamePrefix` n
,\n -> n `Set.member` visibleDecls && pfx `isNamePrefix` n)
browseTSyns visibleType iface disp
browseNewtypes visibleType iface disp
browseVars visibleDecl iface disp
browseTSyns :: (M.Name -> Bool) -> M.IfaceDecls -> NameDisp -> REPL ()
browseTSyns isVisible M.IfaceDecls { .. } names = do
let tsyns = sortBy (M.cmpNameDisplay names `on` T.tsName)
[ ts | ts <- Map.elems ifTySyns, isVisible (T.tsName ts) ]
unless (null tsyns) $ do
rPutStrLn "Type Synonyms"
rPutStrLn "============="
rPrint (runDoc names (nest 4 (vcat (map pp tsyns))))
rPutStrLn ""
browseNewtypes :: (M.Name -> Bool) -> M.IfaceDecls -> NameDisp -> REPL ()
browseNewtypes isVisible M.IfaceDecls { .. } names = do
let nts = sortBy (M.cmpNameDisplay names `on` T.ntName)
[ nt | nt <- Map.elems ifNewtypes, isVisible (T.ntName nt) ]
unless (null nts) $ do
rPutStrLn "Newtypes"
rPutStrLn "========"
rPrint (runDoc names (nest 4 (vcat (map T.ppNewtypeShort nts))))
rPutStrLn ""
browseVars :: (M.Name -> Bool) -> M.IfaceDecls -> NameDisp -> REPL ()
browseVars isVisible M.IfaceDecls { .. } names = do
let vars = sortBy (M.cmpNameDisplay names `on` M.ifDeclName)
[ d | d <- Map.elems ifDecls, isVisible (M.ifDeclName d) ]
let isProp p = T.PragmaProperty `elem` (M.ifDeclPragmas p)
(props,syms) = partition isProp vars
ppBlock "Properties" props
ppBlock "Symbols" syms
where
ppBlock name xs = unless (null xs) $
do rPutStrLn name
rPutStrLn (replicate (length name) '=')
let ppVar M.IfaceDecl { .. } = pp ifDeclName <+> char ':' <+> pp ifDeclSig
rPrint (runDoc names (nest 4 (vcat (map ppVar xs))))
rPutStrLn ""
setOptionCmd :: String -> REPL ()
setOptionCmd str
| Just value <- mbValue = setUser key value
| null key = mapM_ (describe . optName) (leaves userOptions)
| otherwise = describe key
where
(before,after) = break (== '=') str
key = trim before
mbValue = case after of
_ : stuff -> Just (trim stuff)
_ -> Nothing
describe k = do
ev <- tryGetUser k
case ev of
Just (EnvString s) -> rPutStrLn (k ++ " = " ++ s)
Just (EnvProg p as) -> rPutStrLn (k ++ " = " ++ intercalate " " (p:as))
Just (EnvNum n) -> rPutStrLn (k ++ " = " ++ show n)
Just (EnvBool True) -> rPutStrLn (k ++ " = on")
Just (EnvBool False) -> rPutStrLn (k ++ " = off")
Nothing -> do rPutStrLn ("Unknown user option: `" ++ k ++ "`")
when (any isSpace k) $ do
let (k1, k2) = break isSpace k
rPutStrLn ("Did you mean: `:set " ++ k1 ++ " =" ++ k2 ++ "`?")
-- XXX at the moment, this can only look at declarations.
helpCmd :: String -> REPL ()
helpCmd cmd
| null cmd = mapM_ rPutStrLn (genHelp commandList)
| otherwise =
case parseHelpName cmd of
Just qname ->
do (env,rnEnv,nameEnv) <- getFocusedEnv
name <- liftModuleCmd (M.renameVar rnEnv qname)
case Map.lookup name (M.ifDecls env) of
Just M.IfaceDecl { .. } ->
do rPutStrLn ""
let property
| P.PragmaProperty `elem` ifDeclPragmas = text "property"
| otherwise = empty
rPrint $ runDoc nameEnv
$ nest 4
$ property
<+> pp qname
<+> colon
<+> pp (ifDeclSig)
case ifDeclDoc of
Just str -> rPutStrLn ('\n' : str)
Nothing -> return ()
Nothing -> rPutStrLn "// No documentation is available."
Nothing ->
rPutStrLn ("Unable to parse name: " ++ cmd)
runShellCmd :: String -> REPL ()
runShellCmd cmd
= io $ do h <- Process.runCommand cmd
_ <- waitForProcess h
return ()
cdCmd :: FilePath -> REPL ()
cdCmd f | null f = rPutStrLn $ "[error] :cd requires a path argument"
| otherwise = do
exists <- io $ doesDirectoryExist f
if exists
then io $ setCurrentDirectory f
else raise $ DirectoryNotFound f
-- C-c Handlings ---------------------------------------------------------------
-- XXX this should probably do something a bit more specific.
handleCtrlC :: REPL ()
handleCtrlC = rPutStrLn "Ctrl-C"
-- Utilities -------------------------------------------------------------------
isNamePrefix :: String -> M.Name -> Bool
isNamePrefix pfx =
let pfx' = ST.pack pfx
in \n -> case M.nameInfo n of
M.Declared _ -> pfx' `ST.isPrefixOf` M.identText (M.nameIdent n)
M.Parameter -> False
{-
printWarning :: (Range,Warning) -> IO ()
printWarning = print . ppWarning
printError :: (Range,Error) -> IO ()
printError = print . ppError
-}
-- | Lift a parsing action into the REPL monad.
replParse :: (String -> Either ParseError a) -> String -> REPL a
replParse parse str = case parse str of
Right a -> return a
Left e -> raise (ParseError e)
replParseInput :: String -> REPL (P.ReplInput P.PName)
replParseInput = replParse (parseReplWith interactiveConfig . T.pack)
replParseExpr :: String -> REPL (P.Expr P.PName)
replParseExpr = replParse (parseExprWith interactiveConfig . T.pack)
interactiveConfig :: Config
interactiveConfig = defaultConfig { cfgSource = "" }
getPrimMap :: REPL M.PrimMap
getPrimMap = liftModuleCmd M.getPrimMap
liftModuleCmd :: M.ModuleCmd a -> REPL a
liftModuleCmd cmd = moduleCmdResult =<< io . cmd =<< getModuleEnv
moduleCmdResult :: M.ModuleRes a -> REPL a
moduleCmdResult (res,ws0) = do
EnvBool warnDefaulting <- getUser "warnDefaulting"
EnvBool warnShadowing <- getUser "warnShadowing"
-- XXX: let's generalize this pattern
let isDefaultWarn (T.DefaultingTo _ _) = True
isDefaultWarn _ = False
filterDefaults w | warnDefaulting = Just w
filterDefaults (M.TypeCheckWarnings xs) =
case filter (not . isDefaultWarn . snd) xs of
[] -> Nothing
ys -> Just (M.TypeCheckWarnings ys)
filterDefaults w = Just w
isShadowWarn (M.SymbolShadowed {}) = True
filterShadowing w | warnShadowing = Just w
filterShadowing (M.RenamerWarnings xs) =
case filter (not . isShadowWarn) xs of
[] -> Nothing
ys -> Just (M.RenamerWarnings ys)
filterShadowing w = Just w
let ws = mapMaybe filterDefaults . mapMaybe filterShadowing $ ws0
(_,_,names) <- getFocusedEnv
mapM_ (rPrint . runDoc names . pp) ws
case res of
Right (a,me') -> setModuleEnv me' >> return a
Left err -> raise (ModuleSystemError names err)
replCheckExpr :: P.Expr P.PName -> REPL (P.Expr M.Name,T.Expr,T.Schema)
replCheckExpr e = liftModuleCmd $ M.checkExpr e
-- | Check declarations as though they were defined at the top-level.
replCheckDecls :: [P.Decl P.PName] -> REPL [T.DeclGroup]
replCheckDecls ds = do
-- check the decls
npds <- liftModuleCmd (M.noPat ds)
let mkTop d = P.Decl P.TopLevel { P.tlExport = P.Public
, P.tlDoc = Nothing
, P.tlValue = d }
(names,ds') <- liftModuleCmd (M.checkDecls (map mkTop npds))
-- extend the naming env
denv <- getDynEnv
setDynEnv denv { M.deNames = names `M.shadowing` M.deNames denv }
return ds'
replSpecExpr :: T.Expr -> REPL T.Expr
replSpecExpr e = liftModuleCmd $ S.specialize e
replEvalExpr :: P.Expr P.PName -> REPL (E.Value, T.Type)
replEvalExpr expr =
do (_,def,sig) <- replCheckExpr expr
me <- getModuleEnv
let cfg = M.meSolverConfig me
mbDef <- io $ CrySAT.withSolver cfg (\s -> defaultReplExpr s def sig)
(def1,ty) <-
case mbDef of
Nothing -> raise (EvalPolyError sig)
Just (tys,def1) ->
do let nms = T.addTNames (T.sVars sig) IntMap.empty
mapM_ (warnDefault nms) tys
let su = T.listSubst [ (T.tpVar a, t) | (a,t) <- tys ]
return (def1, T.apSubst su (T.sType sig))
val <- liftModuleCmd (M.evalExpr def1)
_ <- io $ rethrowEvalError $ X.evaluate val
whenDebug (rPutStrLn (dump def1))
-- add "it" to the namespace
bindItVariable ty def1
return (val,ty)
where
warnDefault ns (x,t) =
rPrint $ text "Assuming" <+> ppWithNames ns x <+> text "=" <+> pp t
itIdent :: M.Ident
itIdent = M.packIdent "it"
replWriteFile :: FilePath -> BS.ByteString -> (X.SomeException -> REPL ()) -> REPL ()
replWriteFile fp bytes handler =
do x <- io $ X.catch (BS.writeFile fp bytes >> return Nothing) (return . Just)
maybe (return ()) handler x
replReadFile :: FilePath -> (X.SomeException -> REPL (Maybe BS.ByteString)) -> REPL (Maybe BS.ByteString)
replReadFile fp handler =
do x <- io $ X.catch (Right `fmap` BS.readFile fp) (\e -> return $ Left e)
either handler (return . Just) x
-- | Creates a fresh binding of "it" to the expression given, and adds
-- it to the current dynamic environment
bindItVariable :: T.Type -> T.Expr -> REPL ()
bindItVariable ty expr = do
freshIt <- freshName itIdent
let schema = T.Forall { T.sVars = []
, T.sProps = []
, T.sType = ty
}
decl = T.Decl { T.dName = freshIt
, T.dSignature = schema
, T.dDefinition = T.DExpr expr
, T.dPragmas = []
, T.dInfix = False
, T.dFixity = Nothing
, T.dDoc = Nothing
}
liftModuleCmd (M.evalDecls [T.NonRecursive decl])
denv <- getDynEnv
let nenv' = M.singletonE (P.UnQual itIdent) freshIt
`M.shadowing` M.deNames denv
setDynEnv $ denv { M.deNames = nenv' }
-- | Creates a fresh binding of "it" to a finite sequence of
-- expressions of the same type, and adds that sequence to the current
-- dynamic environment
bindItVariables :: T.Type -> [T.Expr] -> REPL ()
bindItVariables ty exprs = bindItVariable seqTy seqExpr
where
len = length exprs
seqTy = T.tSeq (T.tNum len) ty
seqExpr = T.EList exprs ty
replEvalDecl :: P.Decl P.PName -> REPL ()
replEvalDecl decl = do
dgs <- replCheckDecls [decl]
whenDebug (mapM_ (\dg -> (rPutStrLn (dump dg))) dgs)
liftModuleCmd (M.evalDecls dgs)
replEdit :: String -> REPL Bool
replEdit file = do
mb <- io (lookupEnv "EDITOR")
let editor = fromMaybe "vim" mb
io $ do
(_,_,_,ph) <- createProcess (shell (unwords [editor, file]))
exit <- waitForProcess ph
return (exit == ExitSuccess)
type CommandMap = Trie CommandDescr
-- Command Parsing -------------------------------------------------------------
-- | Strip leading space.
sanitize :: String -> String
sanitize = dropWhile isSpace
-- | Strip trailing space.
sanitizeEnd :: String -> String
sanitizeEnd = reverse . sanitize . reverse
trim :: String -> String
trim = sanitizeEnd . sanitize
-- | Split at the first word boundary.
splitCommand :: String -> Maybe (String,String)
splitCommand txt =
case sanitize txt of
':' : more
| (as,bs) <- span (\x -> isPunctuation x || isSymbol x) more
, not (null as) -> Just (':' : as, sanitize bs)
| (as,bs) <- break isSpace more
, not (null as) -> Just (':' : as, sanitize bs)
| otherwise -> Nothing
expr -> guard (not (null expr)) >> return (expr,[])
-- | Uncons a list.
uncons :: [a] -> Maybe (a,[a])
uncons as = case as of
a:rest -> Just (a,rest)
_ -> Nothing
-- | Lookup a string in the command list.
findCommand :: String -> [CommandDescr]
findCommand str = lookupTrie str commands
-- | Lookup a string in the command list, returning an exact match
-- even if it's the prefix of another command.
findCommandExact :: String -> [CommandDescr]
findCommandExact str = lookupTrieExact str commands
-- | Lookup a string in the notebook-safe command list.
findNbCommand :: Bool -> String -> [CommandDescr]
findNbCommand True str = lookupTrieExact str nbCommands
findNbCommand False str = lookupTrie str nbCommands
-- | Parse a line as a command.
parseCommand :: (String -> [CommandDescr]) -> String -> Maybe Command
parseCommand findCmd line = do
(cmd,args) <- splitCommand line
let args' = sanitizeEnd args
case findCmd cmd of
[c] -> case cBody c of
ExprArg body -> Just (Command (body args'))
DeclsArg body -> Just (Command (body args'))
ExprTypeArg body -> Just (Command (body args'))
FilenameArg body -> Just (Command (body =<< expandHome args'))
OptionArg body -> Just (Command (body args'))
ShellArg body -> Just (Command (body args'))
NoArg body -> Just (Command body)
FileExprArg body ->
case extractFilePath args' of
Just (fp,expr) -> Just (Command (expandHome fp >>= flip body expr))
Nothing -> Nothing
[] -> case uncons cmd of
Just (':',_) -> Just (Unknown cmd)
Just _ -> Just (Command (evalCmd line))
_ -> Nothing
cs -> Just (Ambiguous cmd (concatMap cNames cs))
where
expandHome path =
case path of
'~' : c : more | isPathSeparator c -> do dir <- io getHomeDirectory
return (dir > more)
_ -> return path
extractFilePath ipt =
let quoted q = (\(a,b) -> (a, drop 1 b)) . break (== q)
in case ipt of
"" -> Nothing
'\'':rest -> Just $ quoted '\'' rest
'"':rest -> Just $ quoted '"' rest
_ -> Just $ break isSpace ipt
cryptol-2.4.0/src/Cryptol/REPL/Monad.hs 0000644 0000000 0000000 00000055034 12737220176 015774 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Cryptol.REPL.Monad (
-- * REPL Monad
REPL(..), runREPL
, io
, raise
, stop
, catch
, rPutStrLn
, rPutStr
, rPrint
-- ** Errors
, REPLException(..)
, rethrowEvalError
-- ** Environment
, getFocusedEnv
, getModuleEnv, setModuleEnv
, getDynEnv, setDynEnv
, uniqify, freshName
, getTSyns, getNewtypes, getVars
, whenDebug
, getExprNames
, getTypeNames
, getPropertyNames
, LoadedModule(..), getLoadedMod, setLoadedMod
, setSearchPath, prependSearchPath
, getPrompt
, shouldContinue
, unlessBatch
, asBatch
, disableLet
, enableLet
, getLetEnabled
, updateREPLTitle
, setUpdateREPLTitle
-- ** Config Options
, EnvVal(..)
, OptionDescr(..)
, setUser, getUser, tryGetUser
, userOptions
, getUserSatNum
-- ** Configurable Output
, getPutStr
, setPutStr
-- ** Smoke Test
, smokeTest
, Smoke(..)
) where
import Cryptol.REPL.Trie
import Cryptol.Eval (EvalError)
import qualified Cryptol.ModuleSystem as M
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.ModuleSystem.Name as M
import qualified Cryptol.ModuleSystem.NamingEnv as M
import Cryptol.Parser (ParseError,ppError)
import Cryptol.Parser.NoInclude (IncludeError,ppIncludeError)
import Cryptol.Parser.NoPat (Error)
import Cryptol.Parser.Position (emptyRange, Range(from))
import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck as T
import qualified Cryptol.Utils.Ident as I
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import qualified Cryptol.Parser.AST as P
import Cryptol.Symbolic (proverNames, lookupProver, SatNum(..))
import Control.Monad (ap,unless,when)
import Control.Monad.Base
import Control.Monad.IO.Class
import Control.Monad.Trans.Control
import Data.Char (isSpace)
import Data.IORef
(IORef,newIORef,readIORef,modifyIORef,atomicModifyIORef)
import Data.List (intercalate, isPrefixOf, unfoldr, sortBy)
import Data.Maybe (catMaybes)
import Data.Ord (comparing)
import Data.Typeable (Typeable)
import System.Directory (findExecutable)
import qualified Control.Exception as X
import qualified Data.Map as Map
import Text.Read (readMaybe)
import Data.SBV.Dynamic (sbvCheckSolverInstallation)
import Prelude ()
import Prelude.Compat
-- REPL Environment ------------------------------------------------------------
data LoadedModule = LoadedModule
{ lName :: Maybe P.ModName -- ^ Focused module
, lPath :: FilePath -- ^ Focused file
}
-- | REPL RW Environment.
data RW = RW
{ eLoadedMod :: Maybe LoadedModule
, eContinue :: Bool
, eIsBatch :: Bool
, eModuleEnv :: M.ModuleEnv
, eUserEnv :: UserEnv
, ePutStr :: String -> IO ()
, eLetEnabled :: Bool
, eUpdateTitle :: REPL ()
}
-- | Initial, empty environment.
defaultRW :: Bool -> IO RW
defaultRW isBatch = do
env <- M.initialModuleEnv
return RW
{ eLoadedMod = Nothing
, eContinue = True
, eIsBatch = isBatch
, eModuleEnv = env
, eUserEnv = mkUserEnv userOptions
, ePutStr = putStr
, eLetEnabled = True
, eUpdateTitle = return ()
}
-- | Build up the prompt for the REPL.
mkPrompt :: RW -> String
mkPrompt rw
| eIsBatch rw = ""
| otherwise = maybe "cryptol" pretty (lName =<< eLoadedMod rw) ++ "> "
-- REPL Monad ------------------------------------------------------------------
-- | REPL_ context with InputT handling.
newtype REPL a = REPL { unREPL :: IORef RW -> IO a }
-- | Run a REPL action with a fresh environment.
runREPL :: Bool -> REPL a -> IO a
runREPL isBatch m = do
ref <- newIORef =<< defaultRW isBatch
unREPL m ref
instance Functor REPL where
{-# INLINE fmap #-}
fmap f m = REPL (\ ref -> fmap f (unREPL m ref))
instance Applicative REPL where
{-# INLINE pure #-}
pure = return
{-# INLINE (<*>) #-}
(<*>) = ap
instance Monad REPL where
{-# INLINE return #-}
return x = REPL (\_ -> return x)
{-# INLINE (>>=) #-}
m >>= f = REPL $ \ref -> do
x <- unREPL m ref
unREPL (f x) ref
instance MonadIO REPL where
liftIO = io
instance MonadBase IO REPL where
liftBase = liftIO
instance MonadBaseControl IO REPL where
type StM REPL a = a
liftBaseWith f = REPL $ \ref ->
f $ \m -> unREPL m ref
restoreM x = return x
instance M.FreshM REPL where
liftSupply f = modifyRW $ \ RW { .. } ->
let (a,s') = f (M.meSupply eModuleEnv)
in (RW { eModuleEnv = eModuleEnv { M.meSupply = s' }, .. },a)
-- Exceptions ------------------------------------------------------------------
-- | REPL exceptions.
data REPLException
= ParseError ParseError
| FileNotFound FilePath
| DirectoryNotFound FilePath
| NoPatError [Error]
| NoIncludeError [IncludeError]
| EvalError EvalError
| ModuleSystemError NameDisp M.ModuleError
| EvalPolyError T.Schema
| TypeNotTestable T.Type
deriving (Show,Typeable)
instance X.Exception REPLException
instance PP REPLException where
ppPrec _ re = case re of
ParseError e -> ppError e
FileNotFound path -> sep [ text "File"
, text ("`" ++ path ++ "'")
, text"not found"
]
DirectoryNotFound path -> sep [ text "Directory"
, text ("`" ++ path ++ "'")
, text"not found or not a directory"
]
NoPatError es -> vcat (map pp es)
NoIncludeError es -> vcat (map ppIncludeError es)
ModuleSystemError ns me -> fixNameDisp ns (pp me)
EvalError e -> pp e
EvalPolyError s -> text "Cannot evaluate polymorphic value."
$$ text "Type:" <+> pp s
TypeNotTestable t -> text "The expression is not of a testable type."
$$ text "Type:" <+> pp t
-- | Raise an exception.
raise :: REPLException -> REPL a
raise exn = io (X.throwIO exn)
catch :: REPL a -> (REPLException -> REPL a) -> REPL a
catch m k = REPL (\ ref -> unREPL m ref `X.catch` \ e -> unREPL (k e) ref)
rethrowEvalError :: IO a -> IO a
rethrowEvalError m = run `X.catch` rethrow
where
run = do
a <- m
return $! a
rethrow :: EvalError -> IO a
rethrow exn = X.throwIO (EvalError exn)
-- Primitives ------------------------------------------------------------------
io :: IO a -> REPL a
io m = REPL (\ _ -> m)
getRW :: REPL RW
getRW = REPL readIORef
modifyRW :: (RW -> (RW,a)) -> REPL a
modifyRW f = REPL (\ ref -> atomicModifyIORef ref f)
modifyRW_ :: (RW -> RW) -> REPL ()
modifyRW_ f = REPL (\ ref -> modifyIORef ref f)
-- | Construct the prompt for the current environment.
getPrompt :: REPL String
getPrompt = mkPrompt `fmap` getRW
-- | Set the name of the currently focused file, edited by @:e@ and loaded via
-- @:r@.
setLoadedMod :: LoadedModule -> REPL ()
setLoadedMod n = do
modifyRW_ (\ rw -> rw { eLoadedMod = Just n })
updateREPLTitle
getLoadedMod :: REPL (Maybe LoadedModule)
getLoadedMod = eLoadedMod `fmap` getRW
setSearchPath :: [FilePath] -> REPL ()
setSearchPath path = do
me <- getModuleEnv
setModuleEnv $ me { M.meSearchPath = path }
prependSearchPath :: [FilePath] -> REPL ()
prependSearchPath path = do
me <- getModuleEnv
setModuleEnv $ me { M.meSearchPath = path ++ M.meSearchPath me }
shouldContinue :: REPL Bool
shouldContinue = eContinue `fmap` getRW
stop :: REPL ()
stop = modifyRW_ (\ rw -> rw { eContinue = False })
unlessBatch :: REPL () -> REPL ()
unlessBatch body = do
rw <- getRW
unless (eIsBatch rw) body
-- | Run a computation in batch mode, restoring the previous isBatch
-- flag afterwards
asBatch :: REPL () -> REPL ()
asBatch body = do
wasBatch <- eIsBatch `fmap` getRW
modifyRW_ $ (\ rw -> rw { eIsBatch = True })
body
modifyRW_ $ (\ rw -> rw { eIsBatch = wasBatch })
disableLet :: REPL ()
disableLet = modifyRW_ (\ rw -> rw { eLetEnabled = False })
enableLet :: REPL ()
enableLet = modifyRW_ (\ rw -> rw { eLetEnabled = True })
-- | Are let-bindings enabled in this REPL?
getLetEnabled :: REPL Bool
getLetEnabled = fmap eLetEnabled getRW
-- | Update the title
updateREPLTitle :: REPL ()
updateREPLTitle = unlessBatch $ do
rw <- getRW
eUpdateTitle rw
-- | Set the function that will be called when updating the title
setUpdateREPLTitle :: REPL () -> REPL ()
setUpdateREPLTitle m = modifyRW_ (\rw -> rw { eUpdateTitle = m })
-- | Set the REPL's string-printer
setPutStr :: (String -> IO ()) -> REPL ()
setPutStr fn = modifyRW_ (\rw -> rw { ePutStr = fn })
-- | Get the REPL's string-printer
getPutStr :: REPL (String -> IO ())
getPutStr = fmap ePutStr getRW
-- | Use the configured output action to print a string
rPutStr :: String -> REPL ()
rPutStr str = do
rw <- getRW
io $ ePutStr rw str
-- | Use the configured output action to print a string with a trailing newline
rPutStrLn :: String -> REPL ()
rPutStrLn str = rPutStr $ str ++ "\n"
-- | Use the configured output action to print something using its Show instance
rPrint :: Show a => a -> REPL ()
rPrint x = rPutStrLn (show x)
getFocusedEnv :: REPL (M.IfaceDecls,M.NamingEnv,NameDisp)
getFocusedEnv = do
me <- getModuleEnv
-- dyNames is a NameEnv that removes the #Uniq prefix from interactively-bound
-- variables.
let (dyDecls,dyNames,dyDisp) = M.dynamicEnv me
let (fDecls,fNames,fDisp) = M.focusedEnv me
return ( dyDecls `mappend` fDecls
, dyNames `M.shadowing` fNames
, dyDisp `mappend` fDisp)
-- -- the subtle part here is removing the #Uniq prefix from
-- -- interactively-bound variables, and also excluding any that are
-- -- shadowed and thus can no longer be referenced
-- let (fDecls,fNames,fDisp) = M.focusedEnv me
-- edecls = M.ifDecls dyDecls
-- -- is this QName something the user might actually type?
-- isShadowed (qn@(P.QName (Just (P.unModName -> ['#':_])) name), _) =
-- case Map.lookup localName neExprs of
-- Nothing -> False
-- Just uniqueNames -> isNamed uniqueNames
-- where localName = P.QName Nothing name
-- isNamed us = any (== qn) (map M.qname us)
-- neExprs = M.neExprs (M.deNames (M.meDynEnv me))
-- isShadowed _ = False
-- unqual ((P.QName _ name), ifds) = (P.QName Nothing name, ifds)
-- edecls' = Map.fromList
-- . map unqual
-- . filter isShadowed
-- $ Map.toList edecls
-- return (decls `mappend` mempty { M.ifDecls = edecls' }, names `mappend` dyNames)
getVars :: REPL (Map.Map M.Name M.IfaceDecl)
getVars = do
(decls,_,_) <- getFocusedEnv
return (M.ifDecls decls)
getTSyns :: REPL (Map.Map M.Name T.TySyn)
getTSyns = do
(decls,_,_) <- getFocusedEnv
return (M.ifTySyns decls)
getNewtypes :: REPL (Map.Map M.Name T.Newtype)
getNewtypes = do
(decls,_,_) <- getFocusedEnv
return (M.ifNewtypes decls)
-- | Get visible variable names.
getExprNames :: REPL [String]
getExprNames =
do (_, fNames, _) <- getFocusedEnv
return (map (show . pp) (Map.keys (M.neExprs fNames)))
-- | Get visible type signature names.
getTypeNames :: REPL [String]
getTypeNames =
do (_, fNames, _) <- getFocusedEnv
return (map (show . pp) (Map.keys (M.neTypes fNames)))
-- | Return a list of property names, sorted by position in the file.
getPropertyNames :: REPL ([M.Name],NameDisp)
getPropertyNames =
do (decls,_,names) <- getFocusedEnv
let xs = M.ifDecls decls
ps = sortBy (comparing (from . M.nameLoc))
$ [ x | (x,d) <- Map.toList xs, T.PragmaProperty `elem` M.ifDeclPragmas d ]
return (ps, names)
getModuleEnv :: REPL M.ModuleEnv
getModuleEnv = eModuleEnv `fmap` getRW
setModuleEnv :: M.ModuleEnv -> REPL ()
setModuleEnv me = modifyRW_ (\rw -> rw { eModuleEnv = me })
getDynEnv :: REPL M.DynamicEnv
getDynEnv = (M.meDynEnv . eModuleEnv) `fmap` getRW
setDynEnv :: M.DynamicEnv -> REPL ()
setDynEnv denv = do
me <- getModuleEnv
setModuleEnv (me { M.meDynEnv = denv })
-- | Given an existing qualified name, prefix it with a
-- relatively-unique string. We make it unique by prefixing with a
-- character @#@ that is not lexically valid in a module name.
uniqify :: M.Name -> REPL M.Name
uniqify name =
case M.nameInfo name of
M.Declared ns ->
M.liftSupply (M.mkDeclared ns (M.nameIdent name) (M.nameFixity name) (M.nameLoc name))
M.Parameter ->
panic "[REPL] uniqify" ["tried to uniqify a parameter: " ++ pretty name]
-- uniqify (P.QName Nothing name) = do
-- i <- eNameSupply `fmap` getRW
-- modifyRW_ (\rw -> rw { eNameSupply = i+1 })
-- let modname' = P.mkModName [ '#' : ("Uniq_" ++ show i) ]
-- return (P.QName (Just modname') name)
-- uniqify qn =
-- panic "[REPL] uniqify" ["tried to uniqify a qualified name: " ++ pretty qn]
-- | Generate a fresh name using the given index. The name will reside within
-- the "" namespace.
freshName :: I.Ident -> REPL M.Name
freshName i = M.liftSupply (M.mkDeclared I.interactiveName i Nothing emptyRange)
-- User Environment Interaction ------------------------------------------------
-- | User modifiable environment, for things like numeric base.
type UserEnv = Map.Map String EnvVal
data EnvVal
= EnvString String
| EnvProg String [String]
| EnvNum !Int
| EnvBool Bool
deriving (Show)
-- | Generate a UserEnv from a description of the options map.
mkUserEnv :: OptionMap -> UserEnv
mkUserEnv opts = Map.fromList $ do
opt <- leaves opts
return (optName opt, optDefault opt)
-- | Set a user option.
setUser :: String -> String -> REPL ()
setUser name val = case lookupTrie name userOptions of
[opt] -> setUserOpt opt
[] -> io (putStrLn ("Unknown env value `" ++ name ++ "`"))
_ -> io (putStrLn ("Ambiguous env value `" ++ name ++ "`"))
where
setUserOpt opt = case optDefault opt of
EnvString _ -> do r <- io (optCheck opt (EnvString val))
case r of
Just err -> io (putStrLn err)
Nothing -> writeEnv (EnvString val)
EnvProg _ _ ->
case splitOptArgs val of
prog:args -> do r <- io (optCheck opt (EnvProg prog args))
case r of
Just err -> io (putStrLn err)
Nothing -> writeEnv (EnvProg prog args)
[] -> io (putStrLn ("Failed to parse command for field, `" ++ name ++ "`"))
EnvNum _ -> case reads val of
[(x,_)] -> do r <- io (optCheck opt (EnvNum x))
case r of
Just err -> io (putStrLn err)
Nothing -> writeEnv (EnvNum x)
_ -> io (putStrLn ("Failed to parse number for field, `" ++ name ++ "`"))
EnvBool _
| any (`isPrefixOf` val) ["enable","on","yes"] ->
writeEnv (EnvBool True)
| any (`isPrefixOf` val) ["disable","off","no"] ->
writeEnv (EnvBool False)
| otherwise ->
io (putStrLn ("Failed to parse boolean for field, `" ++ name ++ "`"))
where
writeEnv ev =
do optEff opt ev
modifyRW_ (\rw -> rw { eUserEnv = Map.insert name ev (eUserEnv rw) })
splitOptArgs :: String -> [String]
splitOptArgs = unfoldr (parse "")
where
parse acc (c:cs) | isQuote c = quoted (c:acc) cs
| not (isSpace c) = parse (c:acc) cs
| otherwise = result acc cs
parse acc [] = result acc []
quoted acc (c:cs) | isQuote c = parse (c:acc) cs
| otherwise = quoted (c:acc) cs
quoted acc [] = result acc []
result [] [] = Nothing
result [] cs = parse [] (dropWhile isSpace cs)
result acc cs = Just (reverse acc, dropWhile isSpace cs)
isQuote :: Char -> Bool
isQuote c = c `elem` ("'\"" :: String)
-- | Get a user option, using Maybe for failure.
tryGetUser :: String -> REPL (Maybe EnvVal)
tryGetUser name = do
rw <- getRW
return (Map.lookup name (eUserEnv rw))
-- | Get a user option, when it's known to exist. Fail with panic when it
-- doesn't.
getUser :: String -> REPL EnvVal
getUser name = do
mb <- tryGetUser name
case mb of
Just ev -> return ev
Nothing -> panic "[REPL] getUser" ["option `" ++ name ++ "` does not exist"]
-- Environment Options ---------------------------------------------------------
type OptionMap = Trie OptionDescr
mkOptionMap :: [OptionDescr] -> OptionMap
mkOptionMap = foldl insert emptyTrie
where
insert m d = insertTrie (optName d) d m
data OptionDescr = OptionDescr
{ optName :: String
, optDefault :: EnvVal
, optCheck :: EnvVal -> IO (Maybe String)
, optHelp :: String
, optEff :: EnvVal -> REPL ()
}
simpleOpt :: String -> EnvVal -> (EnvVal -> IO (Maybe String)) -> String
-> OptionDescr
simpleOpt optName optDefault optCheck optHelp =
OptionDescr { optEff = \ _ -> return (), .. }
userOptions :: OptionMap
userOptions = mkOptionMap
[ simpleOpt "base" (EnvNum 16) checkBase
"the base to display words at"
, simpleOpt "debug" (EnvBool False) (const $ return Nothing)
"enable debugging output"
, simpleOpt "ascii" (EnvBool False) (const $ return Nothing)
"display 7- or 8-bit words using ASCII notation."
, simpleOpt "infLength" (EnvNum 5) checkInfLength
"The number of elements to display for infinite sequences."
, simpleOpt "tests" (EnvNum 100) (const $ return Nothing)
"The number of random tests to try."
, simpleOpt "satNum" (EnvString "1") checkSatNum
"The maximum number of :sat solutions to display (\"all\" for no limit)."
, simpleOpt "prover" (EnvString "z3") checkProver $
"The external SMT solver for :prove and :sat (" ++ proverListString ++ ")."
, simpleOpt "warnDefaulting" (EnvBool True) (const $ return Nothing)
"Choose if we should display warnings when defaulting."
, simpleOpt "warnShadowing" (EnvBool True) (const $ return Nothing)
"Choose if we should display warnings when shadowing symbols."
, simpleOpt "smtfile" (EnvString "-") (const $ return Nothing)
"The file to use for SMT-Lib scripts (for debugging or offline proving)"
, OptionDescr "mono-binds" (EnvBool True) (const $ return Nothing)
"Whether or not to generalize bindings in a where-clause" $
\case EnvBool b -> do me <- getModuleEnv
setModuleEnv me { M.meMonoBinds = b }
_ -> return ()
, OptionDescr "tc-solver" (EnvProg "z3" [ "-smt2", "-in" ])
(const (return Nothing)) -- TODO: check for the program in the path
"The solver that will be used by the type checker" $
\case EnvProg prog args -> do me <- getModuleEnv
let cfg = M.meSolverConfig me
setModuleEnv me { M.meSolverConfig =
cfg { T.solverPath = prog
, T.solverArgs = args } }
_ -> return ()
, OptionDescr "tc-debug" (EnvNum 0)
(const (return Nothing))
"Enable type-checker debugging output" $
\case EnvNum n -> do me <- getModuleEnv
let cfg = M.meSolverConfig me
setModuleEnv me { M.meSolverConfig = cfg{ T.solverVerbose = fromIntegral n } }
_ -> return ()
, OptionDescr "core-lint" (EnvBool False)
(const (return Nothing))
"Enable sanity checking of type-checker" $
let setIt x = do me <- getModuleEnv
setModuleEnv me { M.meCoreLint = x }
in \case EnvBool True -> setIt M.CoreLint
EnvBool False -> setIt M.NoCoreLint
_ -> return ()
]
-- | Check the value to the `base` option.
checkBase :: EnvVal -> IO (Maybe String)
checkBase val = case val of
EnvNum n
| n >= 2 && n <= 36 -> return Nothing
| otherwise -> return $ Just "base must fall between 2 and 36"
_ -> return $ Just "unable to parse a value for base"
checkInfLength :: EnvVal -> IO (Maybe String)
checkInfLength val = case val of
EnvNum n
| n >= 0 -> return Nothing
| otherwise -> return $ Just "the number of elements should be positive"
_ -> return $ Just "unable to parse a value for infLength"
checkProver :: EnvVal -> IO (Maybe String)
checkProver val = case val of
EnvString s
| s `notElem` proverNames -> return $ Just $ "Prover must be " ++ proverListString
| s `elem` ["offline", "any"] -> return Nothing
| otherwise -> do let prover = lookupProver s
available <- sbvCheckSolverInstallation prover
unless available $
putStrLn $ "Warning: " ++ s ++ " installation not found"
return Nothing
_ -> return $ Just "unable to parse a value for prover"
proverListString :: String
proverListString = concatMap (++ ", ") (init proverNames) ++ "or " ++ last proverNames
checkSatNum :: EnvVal -> IO (Maybe String)
checkSatNum val = case val of
EnvString "all" -> return Nothing
EnvString s ->
case readMaybe s :: Maybe Int of
Just n | n >= 1 -> return Nothing
_ -> return $ Just "must be an integer > 0 or \"all\""
_ -> return $ Just "unable to parse a value for satNum"
getUserSatNum :: REPL SatNum
getUserSatNum = do
EnvString s <- getUser "satNum"
case s of
"all" -> return AllSat
_ | Just n <- readMaybe s -> return (SomeSat n)
_ -> panic "REPL.Monad.getUserSatNum"
[ "invalid satNum option" ]
-- Environment Utilities -------------------------------------------------------
whenDebug :: REPL () -> REPL ()
whenDebug m = do
EnvBool b <- getUser "debug"
when b m
-- Smoke Testing ---------------------------------------------------------------
smokeTest :: REPL [Smoke]
smokeTest = catMaybes <$> sequence tests
where
tests = [ z3exists ]
type SmokeTest = REPL (Maybe Smoke)
data Smoke
= Z3NotFound
deriving (Show, Eq)
instance PP Smoke where
ppPrec _ smoke =
case smoke of
Z3NotFound -> text . intercalate " " $ [
"[error] z3 is required to run Cryptol, but was not found in the"
, "system path. See the Cryptol README for more on how to install z3."
]
z3exists :: SmokeTest
z3exists = do
mPath <- io $ findExecutable "z3"
case mPath of
Nothing -> return (Just Z3NotFound)
Just _ -> return Nothing
cryptol-2.4.0/src/Cryptol/REPL/Trie.hs 0000644 0000000 0000000 00000003305 12737220176 015633 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.REPL.Trie where
import Cryptol.Utils.Panic (panic)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe,maybeToList)
-- | Maps string names to values, allowing for partial key matches and querying.
data Trie a = Node (Map.Map Char (Trie a)) (Maybe a)
deriving (Show)
emptyTrie :: Trie a
emptyTrie = Node Map.empty Nothing
-- | Insert a value into the Trie. Will call `panic` if a value already exists
-- with that key.
insertTrie :: String -> a -> Trie a -> Trie a
insertTrie k a = loop k
where
loop key (Node m mb) = case key of
c:cs -> Node (Map.alter (Just . loop cs . fromMaybe emptyTrie) c m) mb
[] -> case mb of
Nothing -> Node m (Just a)
Just _ -> panic "[REPL] Trie" ["key already exists:", "\t" ++ k]
-- | Return all matches with the given prefix.
lookupTrie :: String -> Trie a -> [a]
lookupTrie key t@(Node mp _) = case key of
c:cs -> case Map.lookup c mp of
Just m' -> lookupTrie cs m'
Nothing -> []
[] -> leaves t
-- | Given a key, return either an exact match for that key, or all
-- matches with the given prefix.
lookupTrieExact :: String -> Trie a -> [a]
lookupTrieExact [] (Node _ (Just x)) = return x
lookupTrieExact [] t = leaves t
lookupTrieExact (c:cs) (Node mp _) =
case Map.lookup c mp of
Just m' -> lookupTrieExact cs m'
Nothing -> []
-- | Return all of the values from a Trie.
leaves :: Trie a -> [a]
leaves (Node mp mb) = maybeToList mb ++ concatMap leaves (Map.elems mp)
cryptol-2.4.0/src/Cryptol/Symbolic/ 0000755 0000000 0000000 00000000000 12737220176 015412 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Symbolic/Prims.hs 0000644 0000000 0000000 00000063314 12737220176 017047 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
module Cryptol.Symbolic.Prims where
import Data.List (genericDrop, genericReplicate, genericSplitAt, genericTake, sortBy, transpose)
import Data.Ord (comparing)
import Cryptol.Eval.Value (BitWord(..))
import Cryptol.Prims.Eval (binary, unary)
import Cryptol.Symbolic.Value
import Cryptol.TypeCheck.AST (Decl(..))
import Cryptol.TypeCheck.Solver.InfNat(Nat'(..), nMul)
import Cryptol.Utils.Panic
import Cryptol.ModuleSystem.Name (asPrim)
import Cryptol.Utils.Ident (Ident,mkIdent)
import qualified Data.SBV as SBV
import qualified Data.SBV.Dynamic as SBV
import qualified Data.Map as Map
import qualified Data.Text as T
import Prelude ()
import Prelude.Compat
traverseSnd :: Functor f => (a -> f b) -> (t, a) -> f (t, b)
traverseSnd f (x, y) = (,) x <$> f y
-- Primitives ------------------------------------------------------------------
evalPrim :: Decl -> Value
evalPrim Decl { dName = n, .. }
| Just prim <- asPrim n, Just val <- Map.lookup prim primTable = val
evalPrim Decl { .. } =
panic "Eval" [ "Unimplemented primitive", show dName ]
-- See also Cryptol.Prims.Eval.primTable
primTable :: Map.Map Ident Value
primTable = Map.fromList $ map (\(n, v) -> (mkIdent (T.pack n), v))
[ ("True" , VBit SBV.svTrue)
, ("False" , VBit SBV.svFalse)
, ("demote" , ecDemoteV) -- Converts a numeric type into its corresponding value.
-- { val, bits } (fin val, fin bits, bits >= width val) => [bits]
, ("+" , binary (arithBinary SBV.svPlus)) -- {a} (Arith a) => a -> a -> a
, ("-" , binary (arithBinary SBV.svMinus)) -- {a} (Arith a) => a -> a -> a
, ("*" , binary (arithBinary SBV.svTimes)) -- {a} (Arith a) => a -> a -> a
, ("/" , binary (arithBinary SBV.svQuot)) -- {a} (Arith a) => a -> a -> a
, ("%" , binary (arithBinary SBV.svRem)) -- {a} (Arith a) => a -> a -> a
, ("^^" , binary (arithBinary sExp)) -- {a} (Arith a) => a -> a -> a
, ("lg2" , unary (arithUnary sLg2)) -- {a} (Arith a) => a -> a
, ("negate" , unary (arithUnary SBV.svUNeg))
, ("<" , binary (cmpBinary cmpLt cmpLt SBV.svFalse))
, (">" , binary (cmpBinary cmpGt cmpGt SBV.svFalse))
, ("<=" , binary (cmpBinary cmpLtEq cmpLtEq SBV.svTrue))
, (">=" , binary (cmpBinary cmpGtEq cmpGtEq SBV.svTrue))
, ("==" , binary (cmpBinary cmpEq cmpEq SBV.svTrue))
, ("!=" , binary (cmpBinary cmpNotEq cmpNotEq SBV.svFalse))
, ("&&" , binary (logicBinary SBV.svAnd SBV.svAnd))
, ("||" , binary (logicBinary SBV.svOr SBV.svOr))
, ("^" , binary (logicBinary SBV.svXOr SBV.svXOr))
, ("complement" , unary (logicUnary SBV.svNot SBV.svNot))
, ("zero" , VPoly zeroV)
, ("<<" , -- {m,n,a} (fin n) => [m] a -> [n] -> [m] a
nlam $ \m ->
tlam $ \_ ->
tlam $ \a ->
VFun $ \xs ->
VFun $ \y ->
case xs of
VWord x -> VWord (SBV.svShiftLeft x (fromVWord y))
_ ->
let shl :: Integer -> Value
shl i =
case m of
Inf -> dropV i xs
Nat j | i >= j -> replicateV j a (zeroV a)
| otherwise -> catV (dropV i xs) (replicateV i a (zeroV a))
in selectV shl y)
, (">>" , -- {m,n,a} (fin n) => [m] a -> [n] -> [m] a
nlam $ \m ->
tlam $ \_ ->
tlam $ \a ->
VFun $ \xs ->
VFun $ \y ->
case xs of
VWord x -> VWord (SBV.svShiftRight x (fromVWord y))
_ ->
let shr :: Integer -> Value
shr i =
case m of
Inf -> catV (replicateV i a (zeroV a)) xs
Nat j | i >= j -> replicateV j a (zeroV a)
| otherwise -> catV (replicateV i a (zeroV a)) (takeV (j - i) xs)
in selectV shr y)
, ("<<<" , -- {m,n,a} (fin m, fin n) => [m] a -> [n] -> [m] a
nlam $ \m ->
tlam $ \_ ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \y ->
case xs of
VWord x -> VWord (SBV.svRotateLeft x (fromVWord y))
_ -> let rol :: Integer -> Value
rol i = catV (dropV k xs) (takeV k xs)
where k = i `mod` finNat' m
in selectV rol y)
, (">>>" , -- {m,n,a} (fin m, fin n) => [m] a -> [n] -> [m] a
nlam $ \m ->
tlam $ \_ ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \y ->
case xs of
VWord x -> VWord (SBV.svRotateRight x (fromVWord y))
_ ->
let ror :: Integer -> Value
ror i = catV (dropV k xs) (takeV k xs)
where k = (- i) `mod` finNat' m
in selectV ror y)
, ("#" , -- {a,b,d} (fin a) => [a] d -> [b] d -> [a + b] d
tlam $ \_ ->
tlam $ \_ ->
tlam $ \_ ->
VFun $ \v1 ->
VFun $ \v2 -> catV v1 v2)
, ("splitAt" , -- {a,b,c} (fin a) => [a+b] c -> ([a]c,[b]c)
nlam $ \(finNat' -> a) ->
nlam $ \_ ->
tlam $ \_ ->
VFun $ \v -> VTuple [takeV a v, dropV a v])
, ("join" , nlam $ \ parts ->
nlam $ \ each ->
tlam $ \ a -> lam (joinV parts each a))
, ("split" , ecSplitV)
, ("reverse" ,
nlam $ \a ->
tlam $ \b ->
lam $ \(fromSeq -> xs) -> toSeq a b (reverse xs))
, ("transpose" ,
nlam $ \a ->
nlam $ \b ->
tlam $ \c ->
lam $ \((map fromSeq . fromSeq) -> xs) ->
case a of
Nat 0 ->
let v = toSeq a c []
in case b of
Nat n -> toSeq b (tvSeq a c) $ genericReplicate n v
Inf -> VStream $ repeat v
_ -> toSeq b (tvSeq a c) $ map (toSeq a c) $ transpose xs)
, ("@" , -- {n,a,i} (fin i) => [n]a -> [i] -> a
tlam $ \_ ->
tlam $ \a ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \y ->
let isInf = case xs of VStream _ -> True; _ -> False
err = zeroV a -- default for out-of-bounds accesses
in atV isInf err (fromSeq xs) y)
, ("@@" , -- {n,a,m,i} (fin i) => [n]a -> [m][i] -> [m]a
tlam $ \_ ->
tlam $ \a ->
tlam $ \_ ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \ys ->
let isInf = case xs of VStream _ -> True; _ -> False
err = zeroV a -- default for out-of-bounds accesses
in atV_list (isTBit a) isInf err (fromSeq xs) ys)
, ("!" , -- {n,a,i} (fin n, fin i) => [n]a -> [i] -> a
tlam $ \_ ->
tlam $ \a ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \y ->
let err = zeroV a -- default for out-of-bounds accesses
isInf = False -- type of (!) guarantess finite sequences
in atV isInf err (reverse $ fromSeq xs) y)
, ("!!" , -- {n,a,m,i} (fin n, fin i) => [n]a -> [m][i] -> [m]a
tlam $ \_ ->
tlam $ \a ->
tlam $ \_ ->
tlam $ \_ ->
VFun $ \xs ->
VFun $ \ys ->
let err = zeroV a -- default for out-of-bounds accesses
isInf = False -- type of (!!) guarantess finite sequences
in atV_list (isTBit a) isInf err (reverse $ fromSeq xs) ys)
, ("fromThen" , fromThenV)
, ("fromTo" , fromToV)
, ("fromThenTo" , fromThenToV)
, ("infFrom" ,
nlam $ \(finNat' -> bits) ->
lam $ \(fromVWord -> first) ->
toStream [ VWord (SBV.svPlus first (literalSWord (fromInteger bits) i)) | i <- [0 ..] ])
, ("infFromThen" , -- {a} (fin a) => [a] -> [a] -> [inf][a]
tlam $ \_ ->
lam $ \(fromVWord -> first) ->
lam $ \(fromVWord -> next) ->
toStream (map VWord (iterate (SBV.svPlus (SBV.svMinus next first)) first)))
-- {at,len} (fin len) => [len][8] -> at
, ("error" ,
tlam $ \at ->
nlam $ \(finNat' -> _len) ->
VFun $ \_msg -> zeroV at) -- error/undefined, is arbitrarily translated to 0
, ("pmult" , -- {a,b} (fin a, fin b) => [a] -> [b] -> [max 1 (a + b) - 1]
nlam $ \(finNat' -> i) ->
nlam $ \(finNat' -> j) ->
VFun $ \v1 ->
VFun $ \v2 ->
let k = max 1 (i + j) - 1
mul _ [] ps = ps
mul as (b:bs) ps = mul (SBV.svFalse : as) bs (ites b (as `addPoly` ps) ps)
xs = map fromVBit (fromSeq v1)
ys = map fromVBit (fromSeq v2)
zs = take (fromInteger k) (mul xs ys [] ++ repeat SBV.svFalse)
in VSeq True (map VBit zs))
, ("pdiv" , -- {a,b} (fin a, fin b) => [a] -> [b] -> [a]
nlam $ \(finNat' -> i) ->
tlam $ \_ ->
VFun $ \v1 ->
VFun $ \v2 ->
let xs = map fromVBit (fromSeq v1)
ys = map fromVBit (fromSeq v2)
zs = take (fromInteger i) (fst (mdp (reverse xs) (reverse ys)) ++ repeat SBV.svFalse)
in VSeq True (map VBit (reverse zs)))
, ("pmod" , -- {a,b} (fin a, fin b) => [a] -> [b+1] -> [b]
nlam $ \_ ->
nlam $ \(finNat' -> j) ->
VFun $ \v1 ->
VFun $ \v2 ->
let xs = map fromVBit (fromSeq v1)
ys = map fromVBit (fromSeq v2)
zs = take (fromInteger j) (snd (mdp (reverse xs) (reverse ys)) ++ repeat SBV.svFalse)
in VSeq True (map VBit (reverse zs)))
, ("random" , panic "Cryptol.Symbolic.Prims.evalECon"
[ "can't symbolically evaluae ECRandom" ])
]
selectV :: (Integer -> Value) -> Value -> Value
selectV f v = sel 0 bits
where
bits = map fromVBit (fromSeq v) -- index bits in big-endian order
sel :: Integer -> [SBool] -> Value
sel offset [] = f offset
sel offset (b : bs) = iteValue b m1 m2
where m1 = sel (offset + 2 ^ length bs) bs
m2 = sel offset bs
asWordList :: [Value] -> Maybe [SWord]
asWordList = go id
where go :: ([SWord] -> [SWord]) -> [Value] -> Maybe [SWord]
go f [] = Just (f [])
go f (VWord x:vs) = go (f . (x:)) vs
go f (VSeq True bs:vs) = go (f . (x:)) vs
where x = packWord $ map fromVBit bs
go _ _ = Nothing
atV_list :: Bool -- Are the elements of the resulting sequence bits?
-> Bool -- Is this an infinite sequence?
-> Value -- default value
-> [Value] -- values to select
-> Value -- index
-> Value
-- Use SBV selection primitives if possible
-- NB: only examine the list if it is finite
atV_list isBit False def (asWordList -> Just ws) v =
case v of
VSeq _ ys ->
VSeq isBit $ map (VWord . SBV.svSelect ws (fromVWord def) . fromVWord) ys
VStream ys ->
VStream $ map (VWord . SBV.svSelect ws (fromVWord def) . fromVWord) ys
_ -> panic "Cryptol.Symbolic.Prims.atV_list" [ "non-mappable value" ]
atV_list isBit _ def xs v =
case v of
VSeq _ ys ->
VSeq isBit $ map (iteAtV def xs) ys
VStream ys ->
VStream $ map (iteAtV def xs) ys
_ -> panic "Cryptol.Symbolic.Prims.atV_list" [ "non-mappable value" ]
atV :: Bool -- Is this an infinite sequence?
-> Value -- default value
-> [Value] -- values to select
-> Value -- index
-> Value
-- When applicable, use the SBV selection operation
-- NB: only examine the list if it is finite
atV False def (asWordList -> Just ws) i =
VWord $ SBV.svSelect ws (fromVWord def) (fromVWord i)
-- Otherwise, decompose into a sequence of if/then/else operations
atV _ def vs i = iteAtV def vs i
-- Select a value at an index by building a sequence of if/then/else operations
iteAtV :: Value -> [Value] -> Value -> Value
iteAtV def vs i =
case i of
VSeq True (map fromVBit -> bits) -> -- index bits in big-endian order
case foldr weave vs bits of
[] -> def
y : _ -> y
VWord x -> foldr f def (zip [0 .. 2 ^ SBV.intSizeOf x - 1] vs)
where
k = SBV.kindOf x
f (n, v) y = iteValue (SBV.svEqual x (SBV.svInteger k n)) v y
_ -> evalPanic "Cryptol.Symbolic.Prims.selectV" ["Invalid index argument"]
where
weave :: SBool -> [Value] -> [Value]
weave _ [] = []
weave b [x1] = [iteValue b def x1]
weave b (x1 : x2 : xs) = iteValue b x2 x1 : weave b xs
replicateV :: Integer -- ^ number of elements
-> TValue -- ^ type of element
-> Value -- ^ element
-> Value
replicateV n TVBit x = VSeq True (genericReplicate n x)
replicateV n _ x = VSeq False (genericReplicate n x)
nth :: a -> [a] -> Int -> a
nth def [] _ = def
nth def (x : xs) n
| n == 0 = x
| otherwise = nth def xs (n - 1)
nthV :: Value -> Value -> Integer -> Value
nthV err v n =
case v of
VStream xs -> nth err xs (fromInteger n)
VSeq _ xs -> nth err xs (fromInteger n)
VWord x -> let i = SBV.intSizeOf x - 1 - fromInteger n
in if i < 0 then err else
VBit (SBV.svTestBit x i)
_ -> err
mapV :: Bool -> (Value -> Value) -> Value -> Value
mapV isBit f v =
case v of
VSeq _ xs -> VSeq isBit (map f xs)
VStream xs -> VStream (map f xs)
_ -> panic "Cryptol.Symbolic.Prims.mapV" [ "non-mappable value" ]
catV :: Value -> Value -> Value
catV xs (VStream ys) = VStream (fromSeq xs ++ ys)
catV (VWord x) ys = VWord (SBV.svJoin x (fromVWord ys))
catV xs (VWord y) = VWord (SBV.svJoin (fromVWord xs) y)
catV (VSeq b xs) (VSeq _ ys) = VSeq b (xs ++ ys)
catV _ _ = panic "Cryptol.Symbolic.Prims.catV" [ "non-concatenable value" ]
dropV :: Integer -> Value -> Value
dropV 0 xs = xs
dropV n xs =
case xs of
VSeq b xs' -> VSeq b (genericDrop n xs')
VStream xs' -> VStream (genericDrop n xs')
VWord w -> VWord $ SBV.svExtract (SBV.intSizeOf w - 1 - fromInteger n) 0 w
_ -> panic "Cryptol.Symbolic.Prims.dropV" [ "non-droppable value" ]
takeV :: Integer -> Value -> Value
takeV n xs =
case xs of
VWord w -> VWord $ SBV.svExtract (SBV.intSizeOf w - 1) (SBV.intSizeOf w - fromInteger n) w
VSeq b xs' -> VSeq b (genericTake n xs')
VStream xs' -> VSeq b (genericTake n xs')
where b = case xs' of VBit _ : _ -> True
_ -> False
_ -> panic "Cryptol.Symbolic.Prims.takeV" [ "non-takeable value" ]
-- | Make a numeric constant.
-- { val, bits } (fin val, fin bits, bits >= width val) => [bits]
ecDemoteV :: Value
ecDemoteV = nlam $ \valT ->
nlam $ \bitT ->
case (valT, bitT) of
(Nat v, Nat bs) -> VWord (literalSWord (fromInteger bs) v)
_ -> evalPanic "Cryptol.Prove.evalECon"
["Unexpected Inf in constant."
, show valT
, show bitT
]
-- Arith -----------------------------------------------------------------------
type Binary = TValue -> Value -> Value -> Value
type Unary = TValue -> Value -> Value
-- | Models functions of type `{a} (Arith a) => a -> a -> a`
arithBinary :: (SWord -> SWord -> SWord) -> Binary
arithBinary op = loop
where
loop ty l r =
case ty of
TVBit -> evalPanic "arithBinop" ["Invalid arguments"]
TVSeq _ TVBit -> VWord (op (fromVWord l) (fromVWord r))
TVSeq _ t -> VSeq False (zipWith (loop t) (fromSeq l) (fromSeq r))
TVStream t -> VStream (zipWith (loop t) (fromSeq l) (fromSeq r))
TVTuple ts -> VTuple (zipWith3 loop ts (fromVTuple l) (fromVTuple r))
TVRec fs -> VRecord [ (f, loop t (lookupRecord f l) (lookupRecord f r)) | (f, t) <- fs ]
TVFun _ t -> VFun (\x -> loop t (fromVFun l x) (fromVFun r x))
-- | Models functions of type `{a} (Arith a) => a -> a`
arithUnary :: (SWord -> SWord) -> Unary
arithUnary op = loop
where
loop ty v =
case ty of
TVBit -> evalPanic "arithUnary" ["Invalid arguments"]
TVSeq _ TVBit -> VWord (op (fromVWord v))
TVSeq _ t -> VSeq False (map (loop t) (fromSeq v))
TVStream t -> VStream (map (loop t) (fromSeq v))
TVTuple ts -> VTuple (zipWith loop ts (fromVTuple v))
TVRec fs -> VRecord [ (f, loop t (lookupRecord f v)) | (f, t) <- fs ]
TVFun _ t -> VFun (\x -> loop t (fromVFun v x))
sExp :: SWord -> SWord -> SWord
sExp x y = go (reverse (unpackWord y)) -- bits in little-endian order
where go [] = literalSWord (SBV.intSizeOf x) 1
go (b : bs) = SBV.svIte b (SBV.svTimes x s) s
where a = go bs
s = SBV.svTimes a a
-- | Ceiling (log_2 x)
sLg2 :: SWord -> SWord
sLg2 x = go 0
where
lit n = literalSWord (SBV.intSizeOf x) n
go i | i < SBV.intSizeOf x = SBV.svIte (SBV.svLessEq x (lit (2^i))) (lit (toInteger i)) (go (i + 1))
| otherwise = lit (toInteger i)
-- Cmp -------------------------------------------------------------------------
cmpValue :: (SBool -> SBool -> a -> a)
-> (SWord -> SWord -> a -> a)
-> (Value -> Value -> a -> a)
cmpValue fb fw = cmp
where
cmp v1 v2 k =
case (v1, v2) of
(VRecord fs1, VRecord fs2) -> let vals = map snd . sortBy (comparing fst)
in cmpValues (vals fs1) (vals fs2) k
(VTuple vs1 , VTuple vs2 ) -> cmpValues vs1 vs2 k
(VBit b1 , VBit b2 ) -> fb b1 b2 k
(VWord w1 , VWord w2 ) -> fw w1 w2 k
(VSeq _ vs1 , VSeq _ vs2 ) -> cmpValues vs1 vs2 k
(VStream {} , VStream {} ) -> panic "Cryptol.Symbolic.Prims.cmpValue"
[ "Infinite streams are not comparable" ]
(VFun {} , VFun {} ) -> panic "Cryptol.Symbolic.Prims.cmpValue"
[ "Functions are not comparable" ]
(VPoly {} , VPoly {} ) -> panic "Cryptol.Symbolic.Prims.cmpValue"
[ "Polymorphic values are not comparable" ]
(VWord w1 , _ ) -> fw w1 (fromVWord v2) k
(_ , VWord w2 ) -> fw (fromVWord v1) w2 k
(_ , _ ) -> panic "Cryptol.Symbolic.Prims.cmpValue"
[ "type mismatch" ]
cmpValues (x1 : xs1) (x2 : xs2) k = cmp x1 x2 (cmpValues xs1 xs2 k)
cmpValues _ _ k = k
cmpEq :: SWord -> SWord -> SBool -> SBool
cmpEq x y k = SBV.svAnd (SBV.svEqual x y) k
cmpNotEq :: SWord -> SWord -> SBool -> SBool
cmpNotEq x y k = SBV.svOr (SBV.svNotEqual x y) k
cmpLt, cmpGt :: SWord -> SWord -> SBool -> SBool
cmpLt x y k = SBV.svOr (SBV.svLessThan x y) (cmpEq x y k)
cmpGt x y k = SBV.svOr (SBV.svGreaterThan x y) (cmpEq x y k)
cmpLtEq, cmpGtEq :: SWord -> SWord -> SBool -> SBool
cmpLtEq x y k = SBV.svAnd (SBV.svLessEq x y) (cmpNotEq x y k)
cmpGtEq x y k = SBV.svAnd (SBV.svGreaterEq x y) (cmpNotEq x y k)
cmpBinary :: (SBool -> SBool -> SBool -> SBool)
-> (SWord -> SWord -> SBool -> SBool)
-> SBool -> Binary
cmpBinary fb fw b _ty v1 v2 = VBit (cmpValue fb fw v1 v2 b)
-- Logic -----------------------------------------------------------------------
errorV :: String -> TValue -> Value
errorV msg = go
where
go ty =
case ty of
TVBit -> VBit (error msg)
TVSeq n t -> VSeq False (replicate (fromInteger n) (go t))
TVStream t -> VStream (repeat (go t))
TVTuple ts -> VTuple [ go t | t <- ts ]
TVRec fs -> VRecord [ (n, go t) | (n, t) <- fs ]
TVFun _ t -> VFun (const (go t))
zeroV :: TValue -> Value
zeroV = go
where
go ty =
case ty of
TVBit -> VBit SBV.svFalse
TVSeq n TVBit -> VWord (literalSWord (fromInteger n) 0)
TVSeq n t -> VSeq False (replicate (fromInteger n) (go t))
TVStream t -> VStream (repeat (go t))
TVTuple ts -> VTuple [ go t | t <- ts ]
TVRec fs -> VRecord [ (n, go t) | (n, t) <- fs ]
TVFun _ t -> VFun (const (go t))
-- | Join a sequence of sequences into a single sequence.
joinV :: Nat' -> Nat' -> TValue -> Value -> Value
joinV parts each a v =
let len = parts `nMul` each
in toSeq len a (concatMap fromSeq (fromSeq v))
-- | Split implementation.
ecSplitV :: Value
ecSplitV =
nlam $ \ parts ->
nlam $ \ each ->
tlam $ \ a ->
lam $ \ v ->
let mkChunks f = map (toFinSeq a) $ f $ fromSeq v
in case (parts, each) of
(Nat p, Nat e) -> VSeq False $ mkChunks (finChunksOf p e)
(Inf , Nat e) -> toStream $ mkChunks (infChunksOf e)
_ -> evalPanic "splitV" ["invalid type arguments to split"]
-- | Split into infinitely many chunks
infChunksOf :: Integer -> [a] -> [[a]]
infChunksOf each xs = let (as,bs) = genericSplitAt each xs
in as : infChunksOf each bs
-- | Split into finitely many chunks
finChunksOf :: Integer -> Integer -> [a] -> [[a]]
finChunksOf 0 _ _ = []
finChunksOf parts each xs = let (as,bs) = genericSplitAt each xs
in as : finChunksOf (parts - 1) each bs
-- | Merge two values given a binop. This is used for and, or and xor.
logicBinary :: (SBool -> SBool -> SBool) -> (SWord -> SWord -> SWord) -> Binary
logicBinary bop op = loop
where
loop ty l r =
case ty of
TVBit -> VBit (bop (fromVBit l) (fromVBit r))
TVSeq _ TVBit -> VWord (op (fromVWord l) (fromVWord r))
TVSeq _ t -> VSeq False (zipWith (loop t) (fromSeq l) (fromSeq r))
TVStream t -> VStream (zipWith (loop t) (fromSeq l) (fromSeq r))
TVTuple ts -> VTuple (zipWith3 loop ts (fromVTuple l) (fromVTuple r))
TVRec fs -> VRecord [ (f, loop t (lookupRecord f l) (lookupRecord f r)) | (f, t) <- fs ]
TVFun _ t -> VFun (\x -> loop t (fromVFun l x) (fromVFun r x))
logicUnary :: (SBool -> SBool) -> (SWord -> SWord) -> Unary
logicUnary bop op = loop
where
loop ty v =
case ty of
TVBit -> VBit (bop (fromVBit v))
TVSeq _ TVBit -> VWord (op (fromVWord v))
TVSeq _ t -> VSeq False (map (loop t) (fromSeq v))
TVStream t -> VStream (map (loop t) (fromSeq v))
TVTuple ts -> VTuple (zipWith loop ts (fromVTuple v))
TVRec fs -> VRecord [ (f, loop t (lookupRecord f v)) | (f, t) <- fs ]
TVFun _ t -> VFun (\x -> loop t (fromVFun v x))
-- @[ 0, 1 .. ]@
fromThenV :: Value
fromThenV =
nlam $ \ first ->
nlam $ \ next ->
nlam $ \ bits ->
nlam $ \ len ->
case (first, next, len, bits) of
(Nat first', Nat next', Nat len', Nat bits') ->
let nums = enumFromThen first' next'
lit i = VWord (literalSWord (fromInteger bits') i)
in VSeq False (genericTake len' (map lit nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- @[ 0 .. 10 ]@
fromToV :: Value
fromToV =
nlam $ \ first ->
nlam $ \ lst ->
nlam $ \ bits ->
case (first, lst, bits) of
(Nat first', Nat lst', Nat bits') ->
let nums = enumFromThenTo first' (first' + 1) lst'
len = 1 + (lst' - first')
lit i = VWord (literalSWord (fromInteger bits') i)
in VSeq False (genericTake len (map lit nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- @[ 0, 1 .. 10 ]@
fromThenToV :: Value
fromThenToV =
nlam $ \ first ->
nlam $ \ next ->
nlam $ \ lst ->
nlam $ \ bits ->
nlam $ \ len ->
case (first, next, lst, len, bits) of
(Nat first', Nat next', Nat lst', Nat len', Nat bits') ->
let nums = enumFromThenTo first' next' lst'
lit i = VWord (literalSWord (fromInteger bits') i)
in VSeq False (genericTake len' (map lit nums))
_ -> evalPanic "fromThenV" ["invalid arguments"]
-- Polynomials -----------------------------------------------------------------
-- TODO: Data.SBV.BitVectors.Polynomials should export ites, addPoly,
-- and mdp (the following definitions are copied from that module)
-- | Add two polynomials
addPoly :: [SBool] -> [SBool] -> [SBool]
addPoly xs [] = xs
addPoly [] ys = ys
addPoly (x:xs) (y:ys) = SBV.svXOr x y : addPoly xs ys
ites :: SBool -> [SBool] -> [SBool] -> [SBool]
ites s xs ys
| Just t <- SBV.svAsBool s
= if t then xs else ys
| True
= go xs ys
where go [] [] = []
go [] (b:bs) = SBV.svIte s SBV.svFalse b : go [] bs
go (a:as) [] = SBV.svIte s a SBV.svFalse : go as []
go (a:as) (b:bs) = SBV.svIte s a b : go as bs
-- conservative over-approximation of the degree
degree :: [SBool] -> Int
degree xs = walk (length xs - 1) $ reverse xs
where walk n [] = n
walk n (b:bs)
| Just t <- SBV.svAsBool b
= if t then n else walk (n-1) bs
| True
= n -- over-estimate
mdp :: [SBool] -> [SBool] -> ([SBool], [SBool])
mdp xs ys = go (length ys - 1) (reverse ys)
where degTop = degree xs
go _ [] = error "SBV.Polynomial.mdp: Impossible happened; exhausted ys before hitting 0"
go n (b:bs)
| n == 0 = (reverse qs, rs)
| True = let (rqs, rrs) = go (n-1) bs
in (ites b (reverse qs) rqs, ites b rs rrs)
where degQuot = degTop - n
ys' = replicate degQuot SBV.svFalse ++ ys
(qs, rs) = divx (degQuot+1) degTop xs ys'
-- return the element at index i; if not enough elements, return false
-- N.B. equivalent to '(xs ++ repeat false) !! i', but more efficient
idx :: [SBool] -> Int -> SBool
idx [] _ = SBV.svFalse
idx (x:_) 0 = x
idx (_:xs) i = idx xs (i-1)
divx :: Int -> Int -> [SBool] -> [SBool] -> ([SBool], [SBool])
divx n _ xs _ | n <= 0 = ([], xs)
divx n i xs ys' = (q:qs, rs)
where q = xs `idx` i
xs' = ites q (xs `addPoly` ys') xs
(qs, rs) = divx (n-1) (i-1) xs' (tail ys')
cryptol-2.4.0/src/Cryptol/Symbolic/Value.hs 0000644 0000000 0000000 00000007643 12737220176 017034 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Cryptol.Symbolic.Value
( SBool, SWord
, literalSWord
, fromBitsLE
, forallBV_, existsBV_
, forallSBool_, existsSBool_
, Value
, TValue(..), isTBit, tvSeq
, GenValue(..), lam, tlam, nlam, toStream, toFinSeq, toSeq, finNat'
, fromVBit, fromVFun, fromVPoly, fromVNumPoly, fromVTuple, fromVRecord
, lookupRecord
, fromSeq, fromVWord
, evalPanic
, iteValue, mergeValue
)
where
import Data.List (foldl')
import Data.SBV.Dynamic
import Cryptol.Eval.Value (TValue(..), isTBit, tvSeq, finNat', GenValue(..),
BitWord(..), lam, tlam, nlam, toStream, toFinSeq, toSeq,
fromSeq, fromVBit, fromVWord, fromVFun, fromVPoly,
fromVNumPoly, fromVTuple, fromVRecord, lookupRecord)
import Cryptol.Utils.Panic (panic)
-- SBool and SWord -------------------------------------------------------------
type SBool = SVal
type SWord = SVal
fromBitsLE :: [SBool] -> SWord
fromBitsLE bs = foldl' f (literalSWord 0 0) bs
where f w b = svJoin (svToWord1 b) w
literalSWord :: Int -> Integer -> SWord
literalSWord w i = svInteger (KBounded False w) i
forallBV_ :: Int -> Symbolic SWord
forallBV_ w = svMkSymVar (Just ALL) (KBounded False w) Nothing
existsBV_ :: Int -> Symbolic SWord
existsBV_ w = svMkSymVar (Just EX) (KBounded False w) Nothing
forallSBool_ :: Symbolic SBool
forallSBool_ = svMkSymVar (Just ALL) KBool Nothing
existsSBool_ :: Symbolic SBool
existsSBool_ = svMkSymVar (Just EX) KBool Nothing
-- Values ----------------------------------------------------------------------
type Value = GenValue SBool SWord
-- Symbolic Conditionals -------------------------------------------------------
iteValue :: SBool -> Value -> Value -> Value
iteValue c x y =
case svAsBool c of
Just True -> x
Just False -> y
Nothing -> mergeValue True c x y
mergeValue :: Bool -> SBool -> Value -> Value -> Value
mergeValue f c v1 v2 =
case (v1, v2) of
(VRecord fs1, VRecord fs2) -> VRecord $ zipWith mergeField fs1 fs2
(VTuple vs1 , VTuple vs2 ) -> VTuple $ zipWith (mergeValue f c) vs1 vs2
(VBit b1 , VBit b2 ) -> VBit $ mergeBit b1 b2
(VWord w1 , VWord w2 ) -> VWord $ mergeWord w1 w2
(VSeq b1 vs1, VSeq _ vs2 ) -> VSeq b1 $ zipWith (mergeValue f c) vs1 vs2
(VStream vs1, VStream vs2) -> VStream $ mergeStream vs1 vs2
(VFun f1 , VFun f2 ) -> VFun $ \x -> mergeValue f c (f1 x) (f2 x)
(VPoly f1 , VPoly f2 ) -> VPoly $ \x -> mergeValue f c (f1 x) (f2 x)
(VWord w1 , _ ) -> VWord $ mergeWord w1 (fromVWord v2)
(_ , VWord w2 ) -> VWord $ mergeWord (fromVWord v1) w2
(_ , _ ) -> panic "Cryptol.Symbolic.Value"
[ "mergeValue: incompatible values" ]
where
mergeBit b1 b2 = svSymbolicMerge KBool f c b1 b2
mergeWord w1 w2 = svSymbolicMerge (kindOf w1) f c w1 w2
mergeField (n1, x1) (n2, x2)
| n1 == n2 = (n1, mergeValue f c x1 x2)
| otherwise = panic "Cryptol.Symbolic.Value"
[ "mergeValue.mergeField: incompatible values" ]
mergeStream xs ys =
mergeValue f c (head xs) (head ys) : mergeStream (tail xs) (tail ys)
-- Big-endian Words ------------------------------------------------------------
instance BitWord SBool SWord where
packWord bs = fromBitsLE (reverse bs)
unpackWord x = [ svTestBit x i | i <- reverse [0 .. intSizeOf x - 1] ]
-- Errors ----------------------------------------------------------------------
evalPanic :: String -> [String] -> a
evalPanic cxt = panic ("[Symbolic]" ++ cxt)
cryptol-2.4.0/src/Cryptol/Testing/ 0000755 0000000 0000000 00000000000 12737220176 015246 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Testing/Concrete.hs 0000644 0000000 0000000 00000013060 12737220176 017344 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE RecordWildCards #-}
module Cryptol.Testing.Concrete where
import Cryptol.Eval.Error
import Cryptol.Eval.Value
import Cryptol.TypeCheck.AST
import Cryptol.Utils.Panic (panic)
import qualified Control.Exception as X
import Data.List(genericReplicate)
import Prelude ()
import Prelude.Compat
-- | A test result is either a pass, a failure due to evaluating to
-- @False@, or a failure due to an exception raised during evaluation
data TestResult
= Pass
| FailFalse [Value]
| FailError EvalError [Value]
isPass :: TestResult -> Bool
isPass Pass = True
isPass _ = False
-- | Apply a testable value to some arguments.
-- Note that this function assumes that the values come from a call to
-- `testableType` (i.e., things are type-correct). We run in the IO
-- monad in order to catch any @EvalError@s.
runOneTest :: Value -> [Value] -> IO TestResult
runOneTest v0 vs0 = run `X.catch` handle
where
run = do
result <- X.evaluate (go v0 vs0)
if result
then return Pass
else return (FailFalse vs0)
handle e = return (FailError e vs0)
go :: Value -> [Value] -> Bool
go (VFun f) (v : vs) = go (f v) vs
go (VFun _) [] = panic "Not enough arguments while applying function"
[]
go (VBit b) [] = b
go v vs = panic "Type error while running test" $
[ "Function:"
, show $ ppValue defaultPPOpts v
, "Arguments:"
] ++ map (show . ppValue defaultPPOpts) vs
{- | Given a (function) type, compute all possible inputs for it.
We also return the total number of test (i.e., the length of the outer list. -}
testableType :: Type -> Maybe (Integer, [[Value]])
testableType ty =
case tNoUser ty of
TCon (TC TCFun) [t1,t2] ->
do sz <- typeSize t1
(tot,vss) <- testableType t2
return (sz * tot, [ v : vs | v <- typeValues t1, vs <- vss ])
TCon (TC TCBit) [] -> return (1, [[]])
_ -> Nothing
{- | Given a fully-evaluated type, try to compute the number of values in it.
Returns `Nothing` for infinite types, user-defined types, polymorhic types,
and, currently, function spaces. Of course, we can easily compute the
sizes of function spaces, but we can't easily enumerate their inhabitants. -}
typeSize :: Type -> Maybe Integer
typeSize ty =
case ty of
TVar _ -> Nothing
TUser _ _ t -> typeSize t
TRec fs -> product <$> mapM (typeSize . snd) fs
TCon (TC tc) ts ->
case (tc, ts) of
(TCNum _, _) -> Nothing
(TCInf, _) -> Nothing
(TCBit, _) -> Just 2
(TCSeq, [sz,el]) -> case tNoUser sz of
TCon (TC (TCNum n)) _ -> (^ n) <$> typeSize el
_ -> Nothing
(TCSeq, _) -> Nothing
(TCFun, _) -> Nothing
(TCTuple _, els) -> product <$> mapM typeSize els
(TCNewtype _, _) -> Nothing
TCon _ _ -> Nothing
{- | Returns all the values in a type. Returns an empty list of values,
for types where 'typeSize' returned 'Nothing'. -}
typeValues :: Type -> [Value]
typeValues ty =
case ty of
TVar _ -> []
TUser _ _ t -> typeValues t
TRec fs -> [ VRecord xs
| xs <- sequence [ [ (f,v) | v <- typeValues t ]
| (f,t) <- fs ]
]
TCon (TC tc) ts ->
case (tc, ts) of
(TCNum _, _) -> []
(TCInf, _) -> []
(TCBit, _) -> [ VBit False, VBit True ]
(TCSeq, ts1) ->
case map tNoUser ts1 of
[ TCon (TC (TCNum n)) _, TCon (TC TCBit) [] ] ->
[ VWord (BV n x) | x <- [ 0 .. 2^n - 1 ] ]
[ TCon (TC (TCNum n)) _, t ] ->
[ VSeq False xs | xs <- sequence $ genericReplicate n
$ typeValues t ]
_ -> []
(TCFun, _) -> [] -- We don't generate function values.
(TCTuple _, els) -> [ VTuple xs | xs <- sequence (map typeValues els)]
(TCNewtype _, _) -> []
TCon _ _ -> []
--------------------------------------------------------------------------------
-- Driver function
data TestSpec m s = TestSpec {
testFn :: Integer -> s -> m (TestResult, s)
, testProp :: String -- ^ The property as entered by the user
, testTotal :: Integer
, testPossible :: Integer
, testRptProgress :: Integer -> Integer -> m ()
, testClrProgress :: m ()
, testRptFailure :: TestResult -> m ()
, testRptSuccess :: m ()
}
data TestReport = TestReport {
reportResult :: TestResult
, reportProp :: String -- ^ The property as entered by the user
, reportTestsRun :: Integer
, reportTestsPossible :: Integer
}
runTests :: Monad m => TestSpec m s -> s -> m TestReport
runTests TestSpec {..} st0 = go 0 st0
where
go testNum _ | testNum >= testTotal = do
testRptSuccess
return $ TestReport Pass testProp testNum testPossible
go testNum st =
do testRptProgress testNum testTotal
res <- testFn (div (100 * (1 + testNum)) testTotal) st
testClrProgress
case res of
(Pass, st') -> do -- delProgress -- unnecessary?
go (testNum + 1) st'
(failure, _st') -> do
testRptFailure failure
return $ TestReport failure testProp testNum testPossible
cryptol-2.4.0/src/Cryptol/Testing/Random.hs 0000644 0000000 0000000 00000011176 12737220176 017030 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- This module generates random values for Cryptol types.
{-# LANGUAGE BangPatterns #-}
module Cryptol.Testing.Random where
import Cryptol.Eval.Value (BV(..),Value,GenValue(..))
import qualified Cryptol.Testing.Concrete as Conc
import Cryptol.TypeCheck.AST (Type(..),TCon(..),TC(..),tNoUser)
import Cryptol.TypeCheck.Solve(simpType)
import Cryptol.Utils.Ident (Ident)
import Control.Monad (forM)
import Data.List (unfoldr, genericTake)
import System.Random (RandomGen, split, random, randomR)
type Gen g = Integer -> g -> (Value, g)
{- | Apply a testable value to some randomly-generated arguments.
Returns `Nothing` if the function returned `True`, or
`Just counterexample` if it returned `False`.
Please note that this function assumes that the generators match
the supplied value, otherwise we'll panic.
-}
runOneTest :: RandomGen g
=> Value -- ^ Function under test
-> [Gen g] -- ^ Argument generators
-> Integer -- ^ Size
-> g
-> IO (Conc.TestResult, g)
runOneTest fun argGens sz g0 = do
let (args, g1) = foldr mkArg ([], g0) argGens
mkArg argGen (as, g) = let (a, g') = argGen sz g in (a:as, g')
result <- Conc.runOneTest fun args
return (result, g1)
{- | Given a (function) type, compute generators for
the function's arguments. Currently we do not support polymorphic functions.
In principle, we could apply these to random types, and test the results. -}
testableType :: RandomGen g => Type -> Maybe [Gen g]
testableType ty =
case tNoUser ty of
TCon (TC TCFun) [t1,t2] ->
do g <- randomValue t1
as <- testableType t2
return (g : as)
TCon (TC TCBit) [] -> return []
_ -> Nothing
{- | A generator for values of the given type. This fails if we are
given a type that lacks a suitable random value generator. -}
randomValue :: RandomGen g => Type -> Maybe (Gen g)
randomValue ty =
case ty of
TCon tc ts ->
case (tc, map (simpType . tNoUser) ts) of
(TC TCBit, []) -> Just randomBit
(TC TCSeq, [TCon (TC TCInf) [], el]) ->
do mk <- randomValue el
return (randomStream mk)
(TC TCSeq, [TCon (TC (TCNum n)) [], TCon (TC TCBit) []]) ->
return (randomWord n)
(TC TCSeq, [TCon (TC (TCNum n)) [], el]) ->
do mk <- randomValue el
return (randomSequence n mk)
(TC (TCTuple _), els) ->
do mks <- mapM randomValue els
return (randomTuple mks)
_ -> Nothing
TVar _ -> Nothing
TUser _ _ t -> randomValue t
TRec fs -> do gs <- forM fs $ \(l,t) -> do g <- randomValue t
return (l,g)
return (randomRecord gs)
-- | Generate a random bit value.
randomBit :: RandomGen g => Gen g
randomBit _ g =
let (b,g1) = random g
in (VBit b, g1)
-- | Generate a random word of the given length (i.e., a value of type @[w]@)
-- The size parameter is assumed to vary between 1 and 100, and we use
-- it to generate smaller numbers first.
randomWord :: RandomGen g => Integer -> Gen g
randomWord w _sz g =
let (val, g1) = randomR (0,2^w-1) g
in (VWord (BV w val), g1)
-- | Generate a random infinite stream value.
randomStream :: RandomGen g => Gen g -> Gen g
randomStream mkElem sz g =
let (g1,g2) = split g
in (VStream (unfoldr (Just . mkElem sz) g1), g2)
{- | Generate a random sequence. Generally, this should be used for sequences
other than bits. For sequences of bits use "randomWord". The difference
is mostly about how the results will be displayed. -}
randomSequence :: RandomGen g => Integer -> Gen g -> Gen g
randomSequence w mkElem sz g =
let (g1,g2) = split g
in (VSeq False $ genericTake w $ unfoldr (Just . mkElem sz) g1 , g2)
-- | Generate a random tuple value.
randomTuple :: RandomGen g => [Gen g] -> Gen g
randomTuple gens sz = go [] gens
where
go els [] g = (VTuple (reverse els), g)
go els (mkElem : more) g =
let (v, g1) = mkElem sz g
in go (v : els) more g1
-- | Generate a random record value.
randomRecord :: RandomGen g => [(Ident, Gen g)] -> Gen g
randomRecord gens sz = go [] gens
where
go els [] g = (VRecord (reverse els), g)
go els ((l,mkElem) : more) g =
let (v, g1) = mkElem sz g
in go ((l,v) : els) more g1
{-
test = do
g <- newStdGen
let (s,_) = randomSequence 100 (randomWord 256) 100 g
print $ ppValue defaultPPOpts { useBase = 16 } s
-}
cryptol-2.4.0/src/Cryptol/Transform/ 0000755 0000000 0000000 00000000000 12737220176 015604 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Transform/MonoValues.hs 0000644 0000000 0000000 00000027420 12737220176 020235 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- This module implements a transformation, which tries to avoid exponential
-- slow down in some cases. What's the problem? Consider the following (common)
-- patterns:
--
-- fibs = [0,1] # [ x + y | x <- fibs, y <- drop`{1} fibs ]
--
-- The type of `fibs` is:
--
-- {a} (a >= 1, fin a) => [inf][a]
--
-- Here `a` is the number of bits to be used in the values computed by `fibs`.
-- When we evaluate `fibs`, `a` becomes a parameter to `fibs`, which works
-- except that now `fibs` is a function, and we don't get any of the memoization
-- we might expect! What looked like an efficient implementation has all
-- of a sudden become exponential!
--
-- Note that this is only a problem for polymorphic values: if `fibs` was
-- already a function, it would not be that surprising that it does not
-- get cached.
--
-- So, to avoid this, we try to spot recursive polymorphic values,
-- where the recursive occurrences have the exact same type parameters
-- as the definition. For example, this is the case in `fibs`: each
-- recursive call to `fibs` is instantiated with exactly the same
-- type parameter (i.e., `a`). The rewrite we do is as follows:
--
-- fibs : {a} (a >= 1, fin a) => [inf][a]
-- fibs = \{a} (a >= 1, fin a) -> fibs'
-- where fibs' : [inf][a]
-- fibs' = [0,1] # [ x + y | x <- fibs', y <- drop`{1} fibs' ]
--
-- After the rewrite, the recursion is monomorphic (i.e., we are always using
-- the same type). As a result, `fibs'` is an ordinary recursive value,
-- where we get the benefit of caching.
--
-- The rewrite is a bit more complex, when there are multiple mutually
-- recursive functions. Here is an example:
--
-- zig : {a} (a >= 2, fin a) => [inf][a]
-- zig = [1] # zag
--
-- zag : {a} (a >= 2, fin a) => [inf][a]
-- zag = [2] # zig
--
-- This gets rewritten to:
--
-- newName : {a} (a >= 2, fin a) => ([inf][a], [inf][a])
-- newName = \{a} (a >= 2, fin a) -> (zig', zag')
-- where
-- zig' : [inf][a]
-- zig' = [1] # zag'
--
-- zag' : [inf][a]
-- zag' = [2] # zig'
--
-- zig : {a} (a >= 2, fin a) => [inf][a]
-- zig = \{a} (a >= 2, fin a) -> (newName a <> <> ).1
--
-- zag : {a} (a >= 2, fin a) => [inf][a]
-- zag = \{a} (a >= 2, fin a) -> (newName a <> <> ).2
--
-- NOTE: We are assuming that no capture would occur with binders.
-- For values, this is because we replaces things with freshly chosen variables.
-- For types, this should be because there should be no shadowing in the types.
-- XXX: Make sure that this really is the case for types!!
{-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Cryptol.Transform.MonoValues (rewModule) where
import Cryptol.ModuleSystem.Name (SupplyT,liftSupply,Supply,mkDeclared)
import Cryptol.Parser.Position (emptyRange)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.TypeMap
import Cryptol.Utils.Ident (ModName)
import Data.List(sortBy,groupBy)
import Data.Either(partitionEithers)
import Data.Map (Map)
import MonadLib hiding (mapM)
import Prelude ()
import Prelude.Compat
{- (f,t,n) |--> x means that when we spot instantiations of `f` with `ts` and
`n` proof argument, we should replace them with `Var x` -}
newtype RewMap' a = RM (Map Name (TypesMap (Map Int a)))
type RewMap = RewMap' Name
instance TrieMap RewMap' (Name,[Type],Int) where
emptyTM = RM emptyTM
nullTM (RM m) = nullTM m
lookupTM (x,ts,n) (RM m) = do tM <- lookupTM x m
tP <- lookupTM ts tM
lookupTM n tP
alterTM (x,ts,n) f (RM m) = RM (alterTM x f1 m)
where
f1 Nothing = do a <- f Nothing
return (insertTM ts (insertTM n a emptyTM) emptyTM)
f1 (Just tM) = Just (alterTM ts f2 tM)
f2 Nothing = do a <- f Nothing
return (insertTM n a emptyTM)
f2 (Just pM) = Just (alterTM n f pM)
unionTM f (RM a) (RM b) = RM (unionTM (unionTM (unionTM f)) a b)
toListTM (RM m) = [ ((x,ts,n),y) | (x,tM) <- toListTM m
, (ts,pM) <- toListTM tM
, (n,y) <- toListTM pM ]
mapMaybeWithKeyTM f (RM m) =
RM (mapWithKeyTM (\qn tm ->
mapWithKeyTM (\tys is ->
mapMaybeWithKeyTM (\i a -> f (qn,tys,i) a) is) tm) m)
-- | Note that this assumes that this pass will be run only once for each
-- module, otherwise we will get name collisions.
rewModule :: Supply -> Module -> (Module,Supply)
rewModule s m = runM body (mName m) s
where
body = do ds <- mapM (rewDeclGroup emptyTM) (mDecls m)
return m { mDecls = ds }
--------------------------------------------------------------------------------
type M = ReaderT RO (SupplyT Id)
type RO = ModName
-- | Produce a fresh top-level name.
newName :: M Name
newName =
do ns <- ask
liftSupply (mkDeclared ns "$mono" Nothing emptyRange)
newTopOrLocalName :: M Name
newTopOrLocalName = newName
-- | Not really any distinction between global and local, all names get the
-- module prefix added, and a unique id.
inLocal :: M a -> M a
inLocal = id
--------------------------------------------------------------------------------
rewE :: RewMap -> Expr -> M Expr -- XXX: not IO
rewE rews = go
where
tryRewrite (EVar x,tps,n) =
do y <- lookupTM (x,tps,n) rews
return (EVar y)
tryRewrite _ = Nothing
go expr =
case expr of
-- Interesting cases
ETApp e t -> case tryRewrite (splitTApp expr 0) of
Nothing -> ETApp <$> go e <*> return t
Just yes -> return yes
EProofApp e -> case tryRewrite (splitTApp e 1) of
Nothing -> EProofApp <$> go e
Just yes -> return yes
EList es t -> EList <$> mapM go es <*> return t
ETuple es -> ETuple <$> mapM go es
ERec fs -> ERec <$> (forM fs $ \(f,e) -> do e1 <- go e
return (f,e1))
ESel e s -> ESel <$> go e <*> return s
EIf e1 e2 e3 -> EIf <$> go e1 <*> go e2 <*> go e3
EComp t e mss -> EComp t <$> go e <*> mapM (mapM (rewM rews)) mss
EVar _ -> return expr
ETAbs x e -> ETAbs x <$> go e
EApp e1 e2 -> EApp <$> go e1 <*> go e2
EAbs x t e -> EAbs x t <$> go e
EProofAbs x e -> EProofAbs x <$> go e
ECast e t -> ECast <$> go e <*> return t
EWhere e dgs -> EWhere <$> go e <*> inLocal
(mapM (rewDeclGroup rews) dgs)
rewM :: RewMap -> Match -> M Match
rewM rews ma =
case ma of
From x t e -> From x t <$> rewE rews e
-- These are not recursive.
Let d -> Let <$> rewD rews d
rewD :: RewMap -> Decl -> M Decl
rewD rews d = do e <- rewDef rews (dDefinition d)
return d { dDefinition = e }
rewDef :: RewMap -> DeclDef -> M DeclDef
rewDef rews (DExpr e) = DExpr <$> rewE rews e
rewDef _ DPrim = return DPrim
rewDeclGroup :: RewMap -> DeclGroup -> M DeclGroup
rewDeclGroup rews dg =
case dg of
NonRecursive d -> NonRecursive <$> rewD rews d
Recursive ds ->
do let (leave,rew) = partitionEithers (map consider ds)
rewGroups = groupBy sameTParams
$ sortBy compareTParams rew
ds1 <- mapM (rewD rews) leave
ds2 <- mapM rewSame rewGroups
return $ Recursive (ds1 ++ concat ds2)
where
sameTParams (_,tps1,x,_) (_,tps2,y,_) = tps1 == tps2 && x == y
compareTParams (_,tps1,x,_) (_,tps2,y,_) = compare (x,tps1) (y,tps2)
consider d =
case dDefinition d of
DPrim -> Left d
DExpr e -> let (tps,props,e') = splitTParams e
in if not (null tps) && notFun e'
then Right (d, tps, props, e')
else Left d
rewSame ds =
do new <- forM ds $ \(d,_,_,e) ->
do x <- newName
return (d, x, e)
let (_,tps,props,_) : _ = ds
tys = map (TVar . tpVar) tps
proofNum = length props
addRew (d,x,_) = insertTM (dName d,tys,proofNum) x
newRews = foldr addRew rews new
newDs <- forM new $ \(d,newN,e) ->
do e1 <- rewE newRews e
return ( d
, d { dName = newN
, dSignature = (dSignature d)
{ sVars = [], sProps = [] }
, dDefinition = DExpr e1
}
)
case newDs of
[(f,f')] ->
return [ f { dDefinition =
let newBody = EVar (dName f')
newE = EWhere newBody
[ Recursive [f'] ]
in DExpr $ foldr ETAbs
(foldr EProofAbs newE props) tps
}
]
_ -> do tupName <- newTopOrLocalName
let (polyDs,monoDs) = unzip newDs
tupAr = length monoDs
addTPs = flip (foldr ETAbs) tps
. flip (foldr EProofAbs) props
-- tuple = \{a} p -> (f',g')
-- where f' = ...
-- g' = ...
tupD = Decl
{ dName = tupName
, dSignature =
Forall tps props $
TCon (TC (TCTuple tupAr))
(map (sType . dSignature) monoDs)
, dDefinition =
DExpr $
addTPs $
EWhere (ETuple [ EVar (dName d) | d <- monoDs ])
[ Recursive monoDs ]
, dPragmas = [] -- ?
, dInfix = False
, dFixity = Nothing
, dDoc = Nothing
}
mkProof e _ = EProofApp e
-- f = \{a} (p) -> (tuple @a p). n
mkFunDef n f =
f { dDefinition =
DExpr $
addTPs $ ESel ( flip (foldl mkProof) props
$ flip (foldl ETApp) tys
$ EVar tupName
) (TupleSel n (Just tupAr))
}
return (tupD : zipWith mkFunDef [ 0 .. ] polyDs)
--------------------------------------------------------------------------------
splitTParams :: Expr -> ([TParam], [Prop], Expr)
splitTParams e = let (tps, e1) = splitWhile splitTAbs e
(props, e2) = splitWhile splitProofAbs e1
in (tps,props,e2)
-- returns type instantitaion and how many "proofs" were there
splitTApp :: Expr -> Int -> (Expr, [Type], Int)
splitTApp (EProofApp e) n = splitTApp e $! (n + 1)
splitTApp e0 n = let (e1,ts) = splitTy e0 []
in (e1, ts, n)
where
splitTy (ETApp e t) ts = splitTy e (t:ts)
splitTy e ts = (e,ts)
notFun :: Expr -> Bool
notFun (EAbs {}) = False
notFun (EProofAbs _ e) = notFun e
notFun _ = True
cryptol-2.4.0/src/Cryptol/Transform/Specialize.hs 0000644 0000000 0000000 00000032257 12737220176 020241 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.Transform.Specialize
where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.TypeMap
import Cryptol.TypeCheck.Subst
import qualified Cryptol.ModuleSystem as M
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.ModuleSystem.Monad as M
import Cryptol.ModuleSystem.Name
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (catMaybes)
import MonadLib hiding (mapM)
import Prelude ()
import Prelude.Compat
-- Specializer Monad -----------------------------------------------------------
-- | A Name should have an entry in the SpecCache iff it is
-- specializable. Each Name starts out with an empty TypesMap.
type SpecCache = Map Name (Decl, TypesMap (Name, Maybe Decl))
-- | The specializer monad.
type SpecT m a = StateT SpecCache (M.ModuleT m) a
type SpecM a = SpecT IO a
runSpecT :: SpecCache -> SpecT m a -> M.ModuleT m (a, SpecCache)
runSpecT s m = runStateT s m
liftSpecT :: Monad m => M.ModuleT m a -> SpecT m a
liftSpecT m = lift m
getSpecCache :: Monad m => SpecT m SpecCache
getSpecCache = get
setSpecCache :: Monad m => SpecCache -> SpecT m ()
setSpecCache = set
modifySpecCache :: Monad m => (SpecCache -> SpecCache) -> SpecT m ()
modifySpecCache = modify
modify :: StateM m s => (s -> s) -> m ()
modify f = get >>= (set . f)
-- Specializer -----------------------------------------------------------------
-- | Add a `where` clause to the given expression containing
-- type-specialized versions of all functions called (transitively) by
-- the body of the expression.
specialize :: Expr -> M.ModuleCmd Expr
specialize expr modEnv = run $ do
let extDgs = allDeclGroups modEnv
let (tparams, expr') = destETAbs expr
spec' <- specializeEWhere expr' extDgs
return (foldr ETAbs spec' tparams)
where
run = M.runModuleT modEnv . fmap fst . runSpecT Map.empty
specializeExpr :: Expr -> SpecM Expr
specializeExpr expr =
case expr of
EList es t -> EList <$> traverse specializeExpr es <*> pure t
ETuple es -> ETuple <$> traverse specializeExpr es
ERec fs -> ERec <$> traverse (traverseSnd specializeExpr) fs
ESel e s -> ESel <$> specializeExpr e <*> pure s
EIf e1 e2 e3 -> EIf <$> specializeExpr e1 <*> specializeExpr e2 <*> specializeExpr e3
EComp t e mss -> EComp t <$> specializeExpr e <*> traverse (traverse specializeMatch) mss
-- Bindings within list comprehensions always have monomorphic types.
EVar {} -> specializeConst expr
ETAbs t e -> do
cache <- getSpecCache
setSpecCache Map.empty
e' <- specializeExpr e
setSpecCache cache
return (ETAbs t e')
-- We need to make sure that after processing `e`, no specialized
-- decls mentioning type variable `t` escape outside the
-- `ETAbs`. To avoid this, we reset to an empty SpecCache while we
-- run `specializeExpr e`, and restore it afterward: this
-- effectively prevents the specializer from registering any type
-- instantiations involving `t` for any decls bound outside the
-- scope of `t`.
ETApp {} -> specializeConst expr
EApp e1 e2 -> EApp <$> specializeExpr e1 <*> specializeExpr e2
EAbs qn t e -> EAbs qn t <$> specializeExpr e
EProofAbs p e -> EProofAbs p <$> specializeExpr e
EProofApp {} -> specializeConst expr
ECast e t -> ECast <$> specializeExpr e <*> pure t
-- TODO: if typeOf e == t, then drop the coercion.
EWhere e dgs -> specializeEWhere e dgs
specializeMatch :: Match -> SpecM Match
specializeMatch (From qn t e) = From qn t <$> specializeExpr e
specializeMatch (Let decl)
| null (sVars (dSignature decl)) = return (Let decl)
| otherwise = fail "unimplemented: specializeMatch Let unimplemented"
-- TODO: should treat this case like EWhere.
-- | Add the declarations to the SpecCache, run the given monadic
-- action, and then pull the specialized declarations back out of the
-- SpecCache state. Return the result along with the declarations and
-- a table of names of specialized bindings.
withDeclGroups :: [DeclGroup] -> SpecM a
-> SpecM (a, [DeclGroup], Map Name (TypesMap Name))
withDeclGroups dgs action = do
origCache <- getSpecCache
let decls = concatMap groupDecls dgs
let newCache = Map.fromList [ (dName d, (d, emptyTM)) | d <- decls ]
let savedCache = Map.intersection origCache newCache
-- We assume that the names bound in dgs are disjoint from the other names in scope.
setSpecCache (Map.union newCache origCache)
result <- action
-- Then reassemble the DeclGroups.
let splitDecl :: Decl -> SpecM [Decl]
splitDecl d = do
Just (_, tm) <- Map.lookup (dName d) <$> getSpecCache
return (catMaybes $ map (snd . snd) $ toListTM tm)
let splitDeclGroup :: DeclGroup -> SpecM [DeclGroup]
splitDeclGroup (Recursive ds) = do
ds' <- concat <$> traverse splitDecl ds
if null ds'
then return []
else return [Recursive ds']
splitDeclGroup (NonRecursive d) = map NonRecursive <$> splitDecl d
dgs' <- concat <$> traverse splitDeclGroup dgs
-- Get updated map of only the local entries we added.
newCache' <- flip Map.intersection newCache <$> getSpecCache
let nameTable = fmap (fmap fst . snd) newCache'
-- Remove local definitions from the cache.
modifySpecCache (Map.union savedCache . flip Map.difference newCache)
return (result, dgs', nameTable)
-- | Compute the specialization of `EWhere e dgs`. A decl within `dgs`
-- is replicated once for each monomorphic type instance at which it
-- is used; decls not mentioned in `e` (even monomorphic ones) are
-- simply dropped.
specializeEWhere :: Expr -> [DeclGroup] -> SpecM Expr
specializeEWhere e dgs = do
(e', dgs', _) <- withDeclGroups dgs (specializeExpr e)
return $ if null dgs'
then e'
else EWhere e' dgs'
-- | Transform the given declaration groups into a set of monomorphic
-- declarations. All of the original declarations with monomorphic
-- types are kept; additionally the result set includes instantiated
-- versions of polymorphic decls that are referenced by the
-- monomorphic bindings. We also return a map relating generated names
-- to the names from the original declarations.
specializeDeclGroups :: [DeclGroup] -> SpecM ([DeclGroup], Map Name (TypesMap Name))
specializeDeclGroups dgs = do
let decls = concatMap groupDecls dgs
let isMono s = null (sVars s) && null (sProps s)
let monos = [ EVar (dName d) | d <- decls, isMono (dSignature d) ]
(_, dgs', names) <- withDeclGroups dgs $ mapM specializeExpr monos
return (dgs', names)
specializeConst :: Expr -> SpecM Expr
specializeConst e0 = do
let (e1, n) = destEProofApps e0
let (e2, ts) = destETApps e1
case e2 of
EVar qname ->
do cache <- getSpecCache
case Map.lookup qname cache of
Nothing -> return e0 -- Primitive/unspecializable variable; leave it alone
Just (decl, tm) ->
case lookupTM ts tm of
Just (qname', _) -> return (EVar qname') -- Already specialized
Nothing -> do -- A new type instance of this function
qname' <- freshName qname ts -- New type instance, record new name
sig' <- instantiateSchema ts n (dSignature decl)
modifySpecCache (Map.adjust (fmap (insertTM ts (qname', Nothing))) qname)
rhs' <- case dDefinition decl of
DExpr e -> do e' <- specializeExpr =<< instantiateExpr ts n e
return (DExpr e')
DPrim -> return DPrim
let decl' = decl { dName = qname', dSignature = sig', dDefinition = rhs' }
modifySpecCache (Map.adjust (fmap (insertTM ts (qname', Just decl'))) qname)
return (EVar qname')
_ -> return e0 -- type/proof application to non-variable; not specializable
-- Utility Functions -----------------------------------------------------------
destEProofApps :: Expr -> (Expr, Int)
destEProofApps = go 0
where
go n (EProofApp e) = go (n + 1) e
go n e = (e, n)
destETApps :: Expr -> (Expr, [Type])
destETApps = go []
where
go ts (ETApp e t) = go (t : ts) e
go ts e = (e, ts)
destEProofAbs :: Expr -> ([Prop], Expr)
destEProofAbs = go []
where
go ps (EProofAbs p e) = go (p : ps) e
go ps e = (ps, e)
destETAbs :: Expr -> ([TParam], Expr)
destETAbs = go []
where
go ts (ETAbs t e) = go (t : ts) e
go ts e = (ts, e)
-- Any top-level declarations in the current module can be found in the
-- ModuleEnv's LoadedModules, and so we can count of freshName to avoid
-- collisions with them. Any generated name for a
-- specialized function will be qualified with the current @ModName@, so genned
-- names will not collide with local decls either.
-- freshName :: Name -> [Type] -> SpecM Name
-- freshName n [] = return n
-- freshName (QName m name) tys = do
-- let name' = reifyName name tys
-- bNames <- matchingBoundNames m
-- let loop i = let nm = name' ++ "_" ++ show i
-- in if nm `elem` bNames
-- then loop $ i + 1
-- else nm
-- let go = if name' `elem` bNames
-- then loop (1 :: Integer)
-- else name'
-- return $ QName m (mkName go)
-- | Freshen a name by giving it a new unique.
freshName :: Name -> [Type] -> SpecM Name
freshName n _ =
case nameInfo n of
Declared ns -> liftSupply (mkDeclared ns ident fx loc)
Parameter -> liftSupply (mkParameter ident loc)
where
fx = nameFixity n
ident = nameIdent n
loc = nameLoc n
-- matchingBoundNames :: (Maybe ModName) -> SpecM [String]
-- matchingBoundNames m = do
-- qns <- allPublicNames <$> liftSpecT M.getModuleEnv
-- return [ unpack n | QName m' (Name n) <- qns , m == m' ]
-- reifyName :: Name -> [Type] -> String
-- reifyName name tys = intercalate "_" (showName name : concatMap showT tys)
-- where
-- tvInt (TVFree i _ _ _) = i
-- tvInt (TVBound i _) = i
-- showT typ =
-- case typ of
-- TCon tc ts -> showTCon tc : concatMap showT ts
-- TUser _ _ t -> showT t
-- TVar tv -> [ "a" ++ show (tvInt tv) ]
-- TRec tr -> "rec" : concatMap showRecFld tr
-- showTCon tCon =
-- case tCon of
-- TC tc -> showTC tc
-- PC pc -> showPC pc
-- TF tf -> showTF tf
-- showPC pc =
-- case pc of
-- PEqual -> "eq"
-- PNeq -> "neq"
-- PGeq -> "geq"
-- PFin -> "fin"
-- PHas sel -> "sel_" ++ showSel sel
-- PArith -> "arith"
-- PCmp -> "cmp"
-- showTC tc =
-- case tc of
-- TCNum n -> show n
-- TCInf -> "inf"
-- TCBit -> "bit"
-- TCSeq -> "seq"
-- TCFun -> "fun"
-- TCTuple n -> "t" ++ show n
-- TCNewtype _ -> "user"
-- showSel sel = intercalate "_" $
-- case sel of
-- TupleSel _ sig -> "tup" : maybe [] ((:[]) . show) sig
-- RecordSel x sig -> "rec" : showName x : map showName (maybe [] id sig)
-- ListSel _ sig -> "list" : maybe [] ((:[]) . show) sig
-- showName nm =
-- case nm of
-- Name s -> unpack s
-- NewName _ n -> "x" ++ show n
-- showTF tf =
-- case tf of
-- TCAdd -> "add"
-- TCSub -> "sub"
-- TCMul -> "mul"
-- TCDiv -> "div"
-- TCMod -> "mod"
-- TCExp -> "exp"
-- TCWidth -> "width"
-- TCMin -> "min"
-- TCMax -> "max"
-- TCLenFromThen -> "len_from_then"
-- TCLenFromThenTo -> "len_from_then_to"
-- showRecFld (nm,t) = showName nm : showT t
instantiateSchema :: [Type] -> Int -> Schema -> SpecM Schema
instantiateSchema ts n (Forall params props ty)
| length params /= length ts = fail "instantiateSchema: wrong number of type arguments"
| length props /= n = fail "instantiateSchema: wrong number of prop arguments"
| otherwise = return $ Forall [] [] (apSubst sub ty)
where sub = listSubst [ (tpVar p, t) | (p, t) <- zip params ts ]
-- | Reduce `length ts` outermost type abstractions and `n` proof abstractions.
instantiateExpr :: [Type] -> Int -> Expr -> SpecM Expr
instantiateExpr [] 0 e = return e
instantiateExpr [] n (EProofAbs _ e) = instantiateExpr [] (n - 1) e
instantiateExpr (t : ts) n (ETAbs param e) =
instantiateExpr ts n (apSubst (singleSubst (tpVar param) t) e)
instantiateExpr _ _ _ = fail "instantiateExpr: wrong number of type/proof arguments"
allDeclGroups :: M.ModuleEnv -> [DeclGroup]
allDeclGroups =
concatMap mDecls
. M.loadedModules
allLoadedModules :: M.ModuleEnv -> [M.LoadedModule]
allLoadedModules =
M.getLoadedModules
. M.meLoadedModules
allPublicNames :: M.ModuleEnv -> [Name]
allPublicNames =
concatMap
( Map.keys
. M.ifDecls
. M.ifPublic
. M.lmInterface
)
. allLoadedModules
traverseSnd :: Functor f => (b -> f c) -> (a, b) -> f (a, c)
traverseSnd f (x, y) = (,) x <$> f y
cryptol-2.4.0/src/Cryptol/TypeCheck/ 0000755 0000000 0000000 00000000000 12737220176 015510 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/TypeCheck/AST.hs 0000644 0000000 0000000 00000067627 12737220176 016515 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric #-}
module Cryptol.TypeCheck.AST
( module Cryptol.TypeCheck.AST
, Name()
, TFun(..)
, Selector(..)
, Import(..)
, ImportSpec(..)
, ExportType(..)
, ExportSpec(..), isExportedBind, isExportedType
, Pragma(..)
, Fixity(..)
, PrimMap(..)
) where
import Cryptol.ModuleSystem.Name
import Cryptol.Prims.Syntax
import Cryptol.Parser.AST ( Selector(..),Pragma(..), ppSelector
, Import(..), ImportSpec(..), ExportType(..)
, ExportSpec(..), isExportedBind
, isExportedType, Fixity(..) )
import Cryptol.Utils.Ident (Ident,isInfixIdent,ModName,packIdent)
import Cryptol.Utils.Panic(panic)
import Cryptol.TypeCheck.PP
import Cryptol.TypeCheck.Solver.InfNat
import GHC.Generics (Generic)
import Control.DeepSeq
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.IntMap as IntMap
import Data.Set (Set)
{- | A Cryptol module.
-}
data Module = Module { mName :: !ModName
, mExports :: ExportSpec Name
, mImports :: [Import]
, mTySyns :: Map Name TySyn
, mNewtypes :: Map Name Newtype
, mDecls :: [DeclGroup]
} deriving (Show, Generic, NFData)
-- | Kinds, classify types.
data Kind = KType
| KNum
| KProp
| Kind :-> Kind
deriving (Eq, Show, Generic, NFData)
infixr 5 :->
-- | The types of polymorphic values.
data Schema = Forall { sVars :: [TParam], sProps :: [Prop], sType :: Type }
deriving (Eq, Show, Generic, NFData)
-- | Type synonym.
data TySyn = TySyn { tsName :: Name -- ^ Name
, tsParams :: [TParam] -- ^ Parameters
, tsConstraints :: [Prop] -- ^ Ensure body is OK
, tsDef :: Type -- ^ Definition
}
deriving (Eq, Show, Generic, NFData)
-- | Named records
data Newtype = Newtype { ntName :: Name
, ntParams :: [TParam]
, ntConstraints :: [Prop]
, ntFields :: [(Ident,Type)]
} deriving (Show, Generic, NFData)
-- | Type parameters.
data TParam = TParam { tpUnique :: !Int -- ^ Parameter identifier
, tpKind :: Kind -- ^ Kind of parameter
, tpName :: Maybe Name -- ^ Name from source, if any.
}
deriving (Show, Generic, NFData)
instance Eq TParam where
x == y = tpUnique x == tpUnique y
instance Ord TParam where
compare x y = compare (tpUnique x) (tpUnique y)
tpVar :: TParam -> TVar
tpVar p = TVBound (tpUnique p) (tpKind p)
-- | The internal representation of types.
-- These are assumed to be kind correct.
data Type = TCon TCon [Type]
-- ^ Type constant with args
| TVar TVar
-- ^ Type variable (free or bound)
| TUser Name [Type] Type
{- ^ This is just a type annotation, for a type that
was written as a type synonym. It is useful so that we
can use it to report nicer errors.
Example: `TUser T ts t` is really just the type `t` that
was written as `T ts` by the user. -}
| TRec [(Ident,Type)]
-- ^ Record type
deriving (Show, Eq, Ord, Generic, NFData)
-- | The type is supposed to be of kind `KProp`
type Prop = Type
-- | The type is "simple" (i.e., it contains no type functions).
type SType = Type
-- | Type variables.
data TVar = TVFree !Int Kind (Set TVar) Doc
-- ^ Unique, kind, ids of bound type variables that are in scope
-- The `Doc` is a description of how this type came to be.
| TVBound !Int Kind
deriving (Show, Generic, NFData)
-- | Type constants.
data TCon = TC TC | PC PC | TF TFun
deriving (Show, Eq, Ord, Generic, NFData)
-- | Built-in type constants.
-- | Predicate symbols.
data PC = PEqual -- ^ @_ == _@
| PNeq -- ^ @_ /= _@
| PGeq -- ^ @_ >= _@
| PFin -- ^ @fin _@
-- classes
| PHas Selector -- ^ @Has sel type field@ does not appear in schemas
| PArith -- ^ @Arith _@
| PCmp -- ^ @Cmp _@
deriving (Show, Eq, Ord, Generic, NFData)
-- | 1-1 constants.
data TC = TCNum Integer -- ^ Numbers
| TCInf -- ^ Inf
| TCBit -- ^ Bit
| TCSeq -- ^ @[_] _@
| TCFun -- ^ @_ -> _@
| TCTuple Int -- ^ @(_, _, _)@
| TCNewtype UserTC -- ^ user-defined, @T@
deriving (Show, Eq, Ord, Generic, NFData)
data UserTC = UserTC Name Kind
deriving (Show, Generic, NFData)
instance Eq UserTC where
UserTC x _ == UserTC y _ = x == y
instance Ord UserTC where
compare (UserTC x _) (UserTC y _) = compare x y
instance Eq TVar where
TVBound x _ == TVBound y _ = x == y
TVFree x _ _ _ == TVFree y _ _ _ = x == y
_ == _ = False
instance Ord TVar where
compare (TVFree x _ _ _) (TVFree y _ _ _) = compare x y
compare (TVFree _ _ _ _) _ = LT
compare _ (TVFree _ _ _ _) = GT
compare (TVBound x _) (TVBound y _) = compare x y
data Expr = EList [Expr] Type -- ^ List value (with type of elements)
| ETuple [Expr] -- ^ Tuple value
| ERec [(Ident,Expr)] -- ^ Record value
| ESel Expr Selector -- ^ Elimination for tuple/record/list
| EIf Expr Expr Expr -- ^ If-then-else
| EComp Type Expr [[Match]] -- ^ List comprehensions
-- The type caches the type of the
-- expr.
| EVar Name -- ^ Use of a bound variable
| ETAbs TParam Expr -- ^ Function Value
| ETApp Expr Type -- ^ Type application
| EApp Expr Expr -- ^ Function application
| EAbs Name Type Expr -- ^ Function value
{- | Proof abstraction. Because we don't keep proofs around
we don't need to name the assumption, but we still need to
record the assumption. The assumption is the `Type` term,
which should be of kind `KProp`.
-}
| EProofAbs {- x -} Prop Expr
{- | If `e : p => t`, then `EProofApp e : t`,
as long as we can prove `p`.
We don't record the actual proofs, as they are not
used for anything. It may be nice to keep them around
for sanity checking.
-}
| EProofApp Expr {- proof -}
{- | if e : t1, then cast e : t2
as long as we can prove that 't1 = t2'.
We could express this in terms of a built-in constant.
`cast :: {a,b} (a =*= b) => a -> b`
Using the constant is a bit verbose though, because we
end up with both the source and target type. So, instead
we use this language construct, which only stores the
target type, and the source type can be reconstructed
from the expression.
Another way to think of this is simply as an expression
with an explicit type annotation.
-}
| ECast Expr Type
| EWhere Expr [DeclGroup]
deriving (Show, Generic, NFData)
data Match = From Name Type Expr -- ^ do we need this type? it seems like it
-- can be computed from the expr
| Let Decl
deriving (Show, Generic, NFData)
data DeclGroup = Recursive [Decl] -- ^ Mutually recursive declarations
| NonRecursive Decl -- ^ Non-recursive declaration
deriving (Show, Generic, NFData)
groupDecls :: DeclGroup -> [Decl]
groupDecls dg = case dg of
Recursive ds -> ds
NonRecursive d -> [d]
data Decl = Decl { dName :: !Name
, dSignature :: Schema
, dDefinition :: DeclDef
, dPragmas :: [Pragma]
, dInfix :: !Bool
, dFixity :: Maybe Fixity
, dDoc :: Maybe String
} deriving (Show, Generic, NFData)
data DeclDef = DPrim
| DExpr Expr
deriving (Show, Generic, NFData)
--------------------------------------------------------------------------------
isFreeTV :: TVar -> Bool
isFreeTV (TVFree {}) = True
isFreeTV _ = False
isBoundTV :: TVar -> Bool
isBoundTV (TVBound {}) = True
isBoundTV _ = False
--------------------------------------------------------------------------------
tIsNat' :: Type -> Maybe Nat'
tIsNat' ty =
case tNoUser ty of
TCon (TC (TCNum x)) [] -> Just (Nat x)
TCon (TC TCInf) [] -> Just Inf
_ -> Nothing
tIsNum :: Type -> Maybe Integer
tIsNum ty = do Nat x <- tIsNat' ty
return x
tIsInf :: Type -> Bool
tIsInf ty = tIsNat' ty == Just Inf
tIsVar :: Type -> Maybe TVar
tIsVar ty = case tNoUser ty of
TVar x -> Just x
_ -> Nothing
tIsFun :: Type -> Maybe (Type, Type)
tIsFun ty = case tNoUser ty of
TCon (TC TCFun) [a, b] -> Just (a, b)
_ -> Nothing
tIsSeq :: Type -> Maybe (Type, Type)
tIsSeq ty = case tNoUser ty of
TCon (TC TCSeq) [n, a] -> Just (n, a)
_ -> Nothing
tIsBit :: Type -> Bool
tIsBit ty = case tNoUser ty of
TCon (TC TCBit) [] -> True
_ -> False
tIsTuple :: Type -> Maybe [Type]
tIsTuple ty = case tNoUser ty of
TCon (TC (TCTuple _)) ts -> Just ts
_ -> Nothing
tIsBinFun :: TFun -> Type -> Maybe (Type,Type)
tIsBinFun f ty = case tNoUser ty of
TCon (TF g) [a,b] | f == g -> Just (a,b)
_ -> Nothing
-- | Split up repeated occurances of the given binary type-level function.
tSplitFun :: TFun -> Type -> [Type]
tSplitFun f t0 = go t0 []
where go ty xs = case tIsBinFun f ty of
Just (a,b) -> go a (go b xs)
Nothing -> ty : xs
pIsFin :: Prop -> Maybe Type
pIsFin ty = case tNoUser ty of
TCon (PC PFin) [t1] -> Just t1
_ -> Nothing
pIsGeq :: Prop -> Maybe (Type,Type)
pIsGeq ty = case tNoUser ty of
TCon (PC PGeq) [t1,t2] -> Just (t1,t2)
_ -> Nothing
pIsEq :: Prop -> Maybe (Type,Type)
pIsEq ty = case tNoUser ty of
TCon (PC PEqual) [t1,t2] -> Just (t1,t2)
_ -> Nothing
pIsArith :: Prop -> Maybe Type
pIsArith ty = case tNoUser ty of
TCon (PC PArith) [t1] -> Just t1
_ -> Nothing
pIsCmp :: Prop -> Maybe Type
pIsCmp ty = case tNoUser ty of
TCon (PC PCmp) [t1] -> Just t1
_ -> Nothing
pIsNumeric :: Prop -> Bool
pIsNumeric (TCon (PC PEqual) _) = True
pIsNumeric (TCon (PC PNeq) _) = True
pIsNumeric (TCon (PC PGeq) _) = True
pIsNumeric (TCon (PC PFin) _) = True
pIsNumeric (TUser _ _ t) = pIsNumeric t
pIsNumeric _ = False
--------------------------------------------------------------------------------
tNum :: Integral a => a -> Type
tNum n = TCon (TC (TCNum (fromIntegral n))) []
tZero :: Type
tZero = tNum (0 :: Int)
tOne :: Type
tOne = tNum (1 :: Int)
tTwo :: Type
tTwo = tNum (2 :: Int)
tInf :: Type
tInf = TCon (TC TCInf) []
tNat' :: Nat' -> Type
tNat' n' = case n' of
Inf -> tInf
Nat n -> tNum n
tBit :: Type
tBit = TCon (TC TCBit) []
tWord :: Type -> Type
tWord a = tSeq a tBit
tSeq :: Type -> Type -> Type
tSeq a b = TCon (TC TCSeq) [a,b]
tChar :: Type
tChar = tWord (tNum (8 :: Int))
tString :: Int -> Type
tString len = tSeq (tNum len) tChar
tRec :: [(Ident,Type)] -> Type
tRec = TRec
tTuple :: [Type] -> Type
tTuple ts = TCon (TC (TCTuple (length ts))) ts
infixr 5 `tFun`
-- | Make a function type.
tFun :: Type -> Type -> Type
tFun a b = TCon (TC TCFun) [a,b]
-- | Eliminate outermost type synonyms.
tNoUser :: Type -> Type
tNoUser t = case t of
TUser _ _ a -> tNoUser a
_ -> t
tWidth :: Type -> Type
tWidth t = TCon (TF TCWidth) [t]
tLenFromThen :: Type -> Type -> Type -> Type
tLenFromThen t1 t2 t3 = TCon (TF TCLenFromThen) [t1,t2,t3]
tLenFromThenTo :: Type -> Type -> Type -> Type
tLenFromThenTo t1 t2 t3 = TCon (TF TCLenFromThenTo) [t1,t2,t3]
tMax :: Type -> Type -> Type
tMax t1 t2 = TCon (TF TCMax) [t1,t2]
infix 4 =#=, >==
infixl 6 .+.
infixl 7 .*.
-- | Equality for numeric types.
(=#=) :: Type -> Type -> Prop
x =#= y = TCon (PC PEqual) [x,y]
(=/=) :: Type -> Type -> Prop
x =/= y = TCon (PC PNeq) [x,y]
pArith :: Type -> Prop
pArith t = TCon (PC PArith) [t]
pCmp :: Type -> Prop
pCmp t = TCon (PC PCmp) [t]
-- | Make a greater-than-or-equal-to constraint.
(>==) :: Type -> Type -> Prop
x >== y = TCon (PC PGeq) [x,y]
-- | A `Has` constraint, used for tuple and record selection.
pHas :: Selector -> Type -> Type -> Prop
pHas l ty fi = TCon (PC (PHas l)) [ty,fi]
pFin :: Type -> Prop
pFin ty = TCon (PC PFin) [ty]
-- | Make multiplication type.
(.*.) :: Type -> Type -> Type
x .*. y = TCon (TF TCMul) [x,y]
-- | Make addition type.
(.+.) :: Type -> Type -> Type
x .+. y = TCon (TF TCAdd) [x,y]
(.-.) :: Type -> Type -> Type
x .-. y = TCon (TF TCSub) [x,y]
(.^.) :: Type -> Type -> Type
x .^. y = TCon (TF TCExp) [x,y]
tDiv :: Type -> Type -> Type
tDiv x y = TCon (TF TCDiv) [x,y]
tMod :: Type -> Type -> Type
tMod x y = TCon (TF TCMod) [x,y]
-- | Make a @min@ type.
tMin :: Type -> Type -> Type
tMin x y = TCon (TF TCMin) [x,y]
newtypeTyCon :: Newtype -> TCon
newtypeTyCon nt = TC $ TCNewtype $ UserTC (ntName nt) (kindOf nt)
newtypeConType :: Newtype -> Schema
newtypeConType nt =
Forall as (ntConstraints nt)
$ TRec (ntFields nt) `tFun` TCon (newtypeTyCon nt) (map (TVar . tpVar) as)
where
as = ntParams nt
-- | Construct a primitive, given a map to the unique names of the Cryptol
-- module.
ePrim :: PrimMap -> Ident -> Expr
ePrim pm n = EVar (lookupPrimDecl n pm)
-- | Make an expression that is `error` pre-applied to a type and a message.
eError :: PrimMap -> Type -> String -> Expr
eError prims t str =
EApp (ETApp (ETApp (ePrim prims (packIdent "error")) t)
(tNum (length str))) (eString prims str)
eString :: PrimMap -> String -> Expr
eString prims str = EList (map (eChar prims) str) tChar
eChar :: PrimMap -> Char -> Expr
eChar prims c = ETApp (ETApp (ePrim prims (packIdent "demote")) (tNum v)) (tNum w)
where v = fromEnum c
w = 8 :: Int
--------------------------------------------------------------------------------
class HasKind t where
kindOf :: t -> Kind
instance HasKind TVar where
kindOf (TVFree _ k _ _) = k
kindOf (TVBound _ k) = k
instance HasKind TCon where
kindOf (TC tc) = kindOf tc
kindOf (PC pc) = kindOf pc
kindOf (TF tf) = kindOf tf
instance HasKind UserTC where
kindOf (UserTC _ k) = k
instance HasKind TC where
kindOf tcon =
case tcon of
TCNum _ -> KNum
TCInf -> KNum
TCBit -> KType
TCSeq -> KNum :-> KType :-> KType
TCFun -> KType :-> KType :-> KType
TCTuple n -> foldr (:->) KType (replicate n KType)
TCNewtype x -> kindOf x
instance HasKind PC where
kindOf pc =
case pc of
PEqual -> KNum :-> KNum :-> KProp
PNeq -> KNum :-> KNum :-> KProp
PGeq -> KNum :-> KNum :-> KProp
PFin -> KNum :-> KProp
PHas _ -> KType :-> KType :-> KProp
PArith -> KType :-> KProp
PCmp -> KType :-> KProp
instance HasKind TFun where
kindOf tfun =
case tfun of
TCWidth -> KNum :-> KNum
TCAdd -> KNum :-> KNum :-> KNum
TCSub -> KNum :-> KNum :-> KNum
TCMul -> KNum :-> KNum :-> KNum
TCDiv -> KNum :-> KNum :-> KNum
TCMod -> KNum :-> KNum :-> KNum
TCExp -> KNum :-> KNum :-> KNum
TCMin -> KNum :-> KNum :-> KNum
TCMax -> KNum :-> KNum :-> KNum
TCLenFromThen -> KNum :-> KNum :-> KNum :-> KNum
TCLenFromThenTo -> KNum :-> KNum :-> KNum :-> KNum
instance HasKind Type where
kindOf ty =
case ty of
TVar a -> kindOf a
TCon c ts -> quickApply (kindOf c) ts
TUser _ _ t -> kindOf t
TRec {} -> KType
instance HasKind TySyn where
kindOf (TySyn _ as _ t) = foldr (:->) (kindOf t) (map kindOf as)
instance HasKind Newtype where
kindOf nt = foldr (:->) KType (map kindOf (ntParams nt))
instance HasKind TParam where
kindOf p = tpKind p
quickApply :: Kind -> [a] -> Kind
quickApply k [] = k
quickApply (_ :-> k) (_ : ts) = quickApply k ts
quickApply k _ = panic "Cryptol.TypeCheck.AST.quickApply"
[ "Applying a non-function kind:", show k ]
-- Pretty Printing -------------------------------------------------------------
instance PP Kind where
ppPrec p k = case k of
KType -> char '*'
KNum -> char '#'
KProp -> text "Prop"
l :-> r -> optParens (p >= 1) (sep [ppPrec 1 l, text "->", ppPrec 0 r])
instance PP (WithNames TVar) where
ppPrec _ (WithNames (TVBound x _) mp) =
case IntMap.lookup x mp of
Just a -> text a
Nothing -> text ("a`" ++ show x)
ppPrec _ (WithNames (TVFree x _ _ _) _) =
char '?' <> text (intToName x)
instance PP TVar where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP TParam where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames TParam) where
ppPrec _ (WithNames p mp) = ppWithNames mp (tpVar p)
instance PP (WithNames Type) where
ppPrec prec ty0@(WithNames ty nmMap) =
case ty of
TVar a -> ppWithNames nmMap a
TRec fs -> braces $ fsep $ punctuate comma
[ pp l <+> text ":" <+> go 0 t | (l,t) <- fs ]
TUser c ts _ -> optParens (prec > 3) $ pp c <+> fsep (map (go 4) ts)
TCon (TC tc) ts ->
case (tc,ts) of
(TCNum n, []) -> integer n
(TCInf, []) -> text "inf"
(TCBit, []) -> text "Bit"
(TCSeq, [t1,TCon (TC TCBit) []]) -> brackets (go 0 t1)
(TCSeq, [t1,t2]) -> optParens (prec > 3)
$ brackets (go 0 t1) <> go 3 t2
(TCFun, [t1,t2]) -> optParens (prec > 1)
$ go 2 t1 <+> text "->" <+> go 1 t2
(TCTuple _, fs) -> parens $ fsep $ punctuate comma $ map (go 0) fs
(_, _) -> pp tc <+> fsep (map (go 4) ts)
TCon (PC pc) ts ->
case (pc,ts) of
(PEqual, [t1,t2]) -> go 0 t1 <+> text "==" <+> go 0 t2
(PNeq , [t1,t2]) -> go 0 t1 <+> text "/=" <+> go 0 t2
(PGeq, [t1,t2]) -> go 0 t1 <+> text ">=" <+> go 0 t2
(PFin, [t1]) -> text "fin" <+> (go 4 t1)
(PHas x, [t1,t2]) -> ppSelector x <+> text "of"
<+> go 0 t1 <+> text "is" <+> go 0 t2
(PArith, [t1]) -> pp pc <+> go 4 t1
(PCmp, [t1]) -> pp pc <+> go 4 t1
(_, _) -> pp pc <+> fsep (map (go 4) ts)
_ | Just tinf <- isTInfix ty0 -> optParens (prec > 2)
$ ppInfix 2 isTInfix tinf
TCon f ts -> optParens (prec > 3)
$ pp f <+> fsep (map (go 4) ts)
where
go p t = ppWithNamesPrec nmMap p t
isTInfix (WithNames (TCon (TF ieOp) [ieLeft',ieRight']) _) =
do let ieLeft = WithNames ieLeft' nmMap
ieRight = WithNames ieRight' nmMap
(ieAssoc,iePrec) <- Map.lookup ieOp tBinOpPrec
return Infix { .. }
isTInfix _ = Nothing
addTNames :: [TParam] -> NameMap -> NameMap
addTNames as ns = foldr (uncurry IntMap.insert) ns
$ named ++ zip unnamed avail
where avail = filter (`notElem` used) (nameList [])
named = [ (u,show (pp n))
| TParam { tpUnique = u, tpName = Just n } <- as ]
unnamed = [ u | TParam { tpUnique = u, tpName = Nothing } <- as ]
used = map snd named ++ IntMap.elems ns
ppNewtypeShort :: Newtype -> Doc
ppNewtypeShort nt =
text "newtype" <+> pp (ntName nt) <+> hsep (map (ppWithNamesPrec nm 9) ps)
where
ps = ntParams nt
nm = addTNames ps emptyNameMap
instance PP Schema where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames Schema) where
ppPrec _ (WithNames s ns) = vars <+> props <+> ppWithNames ns1 (sType s)
where
vars = case sVars s of
[] -> empty
vs -> braces $ commaSep $ map (ppWithNames ns1) vs
props = case sProps s of
[] -> empty
ps -> parens (commaSep (map (ppWithNames ns1) ps)) <+> text "=>"
ns1 = addTNames (sVars s) ns
instance PP TySyn where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames TySyn) where
ppPrec _ (WithNames (TySyn n ps _ ty) ns) =
text "type" <+> pp n <+> sep (map (ppWithNames ns1) ps) <+> char '='
<+> ppWithNames ns1 ty
where ns1 = addTNames ps ns
instance PP Type where
ppPrec n t = ppWithNamesPrec IntMap.empty n t
instance PP TCon where
ppPrec _ (TC tc) = pp tc
ppPrec _ (PC tc) = pp tc
ppPrec _ (TF tc) = pp tc
instance PP PC where
ppPrec _ x =
case x of
PEqual -> text "(==)"
PNeq -> text "(/=)"
PGeq -> text "(>=)"
PFin -> text "fin"
PHas sel -> parens (ppSelector sel)
PArith -> text "Arith"
PCmp -> text "Cmp"
instance PP TC where
ppPrec _ x =
case x of
TCNum n -> integer n
TCInf -> text "inf"
TCBit -> text "Bit"
TCSeq -> text "[]"
TCFun -> text "(->)"
TCTuple 0 -> text "()"
TCTuple 1 -> text "(one tuple?)"
TCTuple n -> parens $ hcat $ replicate (n-1) comma
TCNewtype u -> pp u
instance PP UserTC where
ppPrec p (UserTC x _) = ppPrec p x
instance PP (WithNames Expr) where
ppPrec prec (WithNames expr nm) =
case expr of
EList [] t -> optParens (prec > 0)
$ text "[]" <+> colon <+> ppWP prec t
EList es _ -> brackets $ sep $ punctuate comma $ map ppW es
ETuple es -> parens $ sep $ punctuate comma $ map ppW es
ERec fs -> braces $ sep $ punctuate comma
[ pp f <+> text "=" <+> ppW e | (f,e) <- fs ]
ESel e sel -> ppWP 4 e <+> text "." <> pp sel
EIf e1 e2 e3 -> optParens (prec > 0)
$ sep [ text "if" <+> ppW e1
, text "then" <+> ppW e2
, text "else" <+> ppW e3 ]
EComp _ e mss -> let arm ms = text "|" <+> commaSep (map ppW ms)
in brackets $ ppW e <+> vcat (map arm mss)
EVar x -> ppPrefixName x
EAbs {} -> let (xs,e) = splitWhile splitAbs expr
in ppLam nm prec [] [] xs e
EProofAbs {} -> let (ps,e1) = splitWhile splitProofAbs expr
(xs,e2) = splitWhile splitAbs e1
in ppLam nm prec [] ps xs e2
ETAbs {} -> let (ts,e1) = splitWhile splitTAbs expr
(ps,e2) = splitWhile splitProofAbs e1
(xs,e3) = splitWhile splitAbs e2
in ppLam nm prec ts ps xs e3
-- infix applications
EApp (EApp (EVar o) a) b
| isInfixIdent (nameIdent o) ->
ppPrec 3 a <+> ppInfixName o <+> ppPrec 3 b
| otherwise ->
ppPrefixName o <+> ppPrec 3 a <+> ppPrec 3 b
EApp e1 e2 -> optParens (prec > 3)
$ ppWP 3 e1 <+> ppWP 4 e2
EProofApp e -> optParens (prec > 3)
$ ppWP 3 e <+> text "<>"
ETApp e t -> optParens (prec > 3)
$ ppWP 3 e <+> ppWP 4 t
ECast e t -> optParens (prec > 0)
( ppWP 2 e <+> text ":" <+> ppW t )
EWhere e ds -> optParens (prec > 0)
( ppW e $$ text "where"
$$ nest 2 (vcat (map ppW ds))
$$ text "" )
where
ppW x = ppWithNames nm x
ppWP x = ppWithNamesPrec nm x
ppLam :: NameMap -> Int -> [TParam] -> [Prop] -> [(Name,Type)] -> Expr -> Doc
ppLam nm prec [] [] [] e = ppWithNamesPrec nm prec e
ppLam nm prec ts ps xs e =
optParens (prec > 0) $
sep [ text "\\" <> tsD <+> psD <+> xsD <+> text "->"
, ppWithNames ns1 e
]
where
ns1 = addTNames ts nm
tsD = if null ts then empty else braces $ sep $ punctuate comma $ map ppT ts
psD = if null ps then empty else parens $ sep $ punctuate comma $ map ppP ps
xsD = if null xs then empty else sep $ map ppArg xs
ppT = ppWithNames ns1
ppP = ppWithNames ns1
ppArg (x,t) = parens (pp x <+> text ":" <+> ppWithNames ns1 t)
splitWhile :: (a -> Maybe (b,a)) -> a -> ([b],a)
splitWhile f e = case f e of
Nothing -> ([], e)
Just (x,e1) -> let (xs,e2) = splitWhile f e1
in (x:xs,e2)
splitAbs :: Expr -> Maybe ((Name,Type), Expr)
splitAbs (EAbs x t e) = Just ((x,t), e)
splitAbs _ = Nothing
splitTAbs :: Expr -> Maybe (TParam, Expr)
splitTAbs (ETAbs t e) = Just (t, e)
splitTAbs _ = Nothing
splitProofAbs :: Expr -> Maybe (Prop, Expr)
splitProofAbs (EProofAbs p e) = Just (p,e)
splitProofAbs _ = Nothing
instance PP Expr where
ppPrec n t = ppWithNamesPrec IntMap.empty n t
instance PP (WithNames Match) where
ppPrec _ (WithNames mat nm) =
case mat of
From x _ e -> pp x <+> text "<-" <+> ppWithNames nm e
Let d -> text "let" <+> ppWithNames nm d
instance PP Match where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames DeclGroup) where
ppPrec _ (WithNames dg nm) =
case dg of
Recursive ds -> text "/* Recursive */"
$$ vcat (map (ppWithNames nm) ds)
$$ text ""
NonRecursive d -> text "/* Not recursive */"
$$ ppWithNames nm d
$$ text ""
instance PP DeclGroup where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames Decl) where
ppPrec _ (WithNames Decl { .. } nm) =
pp dName <+> text ":" <+> ppWithNames nm dSignature $$
(if null dPragmas
then empty
else text "pragmas" <+> pp dName <+> sep (map pp dPragmas)
) $$
pp dName <+> text "=" <+> ppWithNames nm dDefinition
instance PP (WithNames DeclDef) where
ppPrec _ (WithNames DPrim _) = text ""
ppPrec _ (WithNames (DExpr e) nm) = ppWithNames nm e
instance PP Decl where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP Module where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames Module) where
ppPrec _ (WithNames Module { .. } nm) =
text "module" <+> pp mName $$
-- XXX: Print exports?
vcat (map pp mImports) $$
-- XXX: Print tysyns
vcat (map (ppWithNames nm) mDecls)
cryptol-2.4.0/src/Cryptol/TypeCheck/Depends.hs 0000644 0000000 0000000 00000012107 12737220176 017427 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE FlexibleInstances #-}
module Cryptol.TypeCheck.Depends where
import Cryptol.ModuleSystem.Name (Name)
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.Position(Range, Located(..), thing)
import Cryptol.Parser.Names (namesB, namesT)
import Cryptol.TypeCheck.Monad( InferM, recordError, getTVars
, Error(..))
import Data.List(sortBy, groupBy)
import Data.Function(on)
import Data.Maybe(mapMaybe)
import Data.Graph.SCC(stronglyConnComp)
import Data.Graph (SCC(..))
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
data TyDecl = TS (P.TySyn Name) | NT (P.Newtype Name)
-- | Check for duplicate and recursive type synonyms.
-- Returns the type-synonyms in dependency order.
orderTyDecls :: [TyDecl] -> InferM [TyDecl]
orderTyDecls ts =
do vs <- getTVars
ds <- combine $ map (toMap vs) ts
let ordered = mkScc [ (t,[x],deps)
| (x,(t,deps)) <- Map.toList (Map.map thing ds) ]
concat `fmap` mapM check ordered
where
toMap vs ty@(NT (P.Newtype x as fs)) =
( thing x
, x { thing = (ty, Set.toList $
Set.difference
(Set.unions (map (namesT vs . P.value) fs))
(Set.fromList (map P.tpName as))
)
}
)
toMap vs ty@(TS (P.TySyn x as t)) =
(thing x
, x { thing = (ty, Set.toList $
Set.difference (namesT vs t)
(Set.fromList (map P.tpName as)))
}
)
getN (TS (P.TySyn x _ _)) = thing x
getN (NT x) = thing (P.nName x)
check (AcyclicSCC x) = return [x]
-- We don't support any recursion, for now.
-- We could support recursion between newtypes, or newtypes and tysysn.
check (CyclicSCC xs) =
do recordError (RecursiveTypeDecls (map getN xs))
return [] -- XXX: This is likely to cause fake errors for missing
-- type synonyms. We could avoid this by, for example, checking
-- for recursive synonym errors, when looking up tycons.
-- | Associate type signatures with bindings and order bindings by dependency.
orderBinds :: [P.Bind Name] -> [SCC (P.Bind Name)]
orderBinds bs = mkScc [ (b, map thing defs, Set.toList uses)
| b <- bs
, let (defs,uses) = namesB b
]
class FromDecl d where
toBind :: d -> Maybe (P.Bind Name)
toTyDecl :: d -> Maybe TyDecl
isTopDecl :: d -> Bool
instance FromDecl (P.TopDecl Name) where
toBind (P.Decl x) = toBind (P.tlValue x)
toBind _ = Nothing
toTyDecl (P.TDNewtype d) = Just (NT (P.tlValue d))
toTyDecl (P.Decl x) = toTyDecl (P.tlValue x)
toTyDecl _ = Nothing
isTopDecl _ = True
instance FromDecl (P.Decl Name) where
toBind (P.DLocated d _) = toBind d
toBind (P.DBind b) = return b
toBind _ = Nothing
toTyDecl (P.DLocated d _) = toTyDecl d
toTyDecl (P.DType x) = Just (TS x)
toTyDecl _ = Nothing
isTopDecl _ = False
{- | Given a list of declarations, annoted with (i) the names that they
define, and (ii) the names that they use, we compute a list of strongly
connected components of the declarations. The SCCs are in dependency order. -}
mkScc :: [(a,[Name],[Name])] -> [SCC a]
mkScc ents = stronglyConnComp $ zipWith mkGr keys ents
where
keys = [ 0 :: Integer .. ]
mkGr i (x,_,uses) = (x,i,mapMaybe (`Map.lookup` nodeMap) uses)
-- Maps names to node ids.
nodeMap = Map.fromList $ concat $ zipWith mkNode keys ents
mkNode i (_,defs,_) = [ (d,i) | d <- defs ]
{- | Combine a bunch of definitions into a single map. Here we check
that each name is defined only onces. -}
combineMaps :: [Map Name (Located a)] -> InferM (Map Name (Located a))
combineMaps ms =
do mapM_ recordError $
do m <- ms
(x,rs) <- duplicates [ a { thing = x } | (x,a) <- Map.toList m ]
return (RepeatedDefinitions x rs)
return (Map.unions ms)
{- | Combine a bunch of definitions into a single map. Here we check
that each name is defined only onces. -}
combine :: [(Name, Located a)] -> InferM (Map Name (Located a))
combine m =
do mapM_ recordError $
do (x,rs) <- duplicates [ a { thing = x } | (x,a) <- m ]
return (RepeatedDefinitions x rs)
return (Map.fromList m)
-- | Identify multiple occurances of something.
duplicates :: Ord a => [Located a] -> [(a,[Range])]
duplicates = mapMaybe multiple
. groupBy ((==) `on` thing)
. sortBy (compare `on` thing)
where
multiple xs@(x : _ : _) = Just (thing x, map srcRange xs)
multiple _ = Nothing
cryptol-2.4.0/src/Cryptol/TypeCheck/Infer.hs 0000644 0000000 0000000 00000070241 12737220176 017113 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Assumes that the `NoPat` pass has been run.
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Infer where
import Cryptol.ModuleSystem.Name (asPrim,lookupPrimDecl)
import Cryptol.Parser.Position
import qualified Cryptol.Parser.AST as P
import qualified Cryptol.Parser.Names as P
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Monad
import Cryptol.TypeCheck.Solve
import Cryptol.TypeCheck.Kind(checkType,checkSchema,checkTySyn,
checkNewtype)
import Cryptol.TypeCheck.Instantiate
import Cryptol.TypeCheck.Depends
import Cryptol.TypeCheck.Subst (listSubst,apSubst,fvs,(@@))
import Cryptol.TypeCheck.Solver.InfNat(genLog)
import Cryptol.Utils.Ident
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.PP
import qualified Data.Map as Map
import Data.Map (Map)
import qualified Data.Set as Set
import Data.Either(partitionEithers)
import Data.Maybe(mapMaybe,isJust, fromMaybe)
import Data.List(partition,find)
import Data.Graph(SCC(..))
import Data.Traversable(forM)
import Control.Monad(when,zipWithM)
inferModule :: P.Module Name -> InferM Module
inferModule m =
inferDs (P.mDecls m) $ \ds1 ->
do simplifyAllConstraints
ts <- getTSyns
nts <- getNewtypes
return Module { mName = thing (P.mName m)
, mExports = P.modExports m
, mImports = map thing (P.mImports m)
, mTySyns = Map.mapMaybe onlyLocal ts
, mNewtypes = Map.mapMaybe onlyLocal nts
, mDecls = ds1
}
where
onlyLocal (IsLocal, x) = Just x
onlyLocal (IsExternal, _) = Nothing
-- | Construct a primitive in the parsed AST.
mkPrim :: String -> InferM (P.Expr Name)
mkPrim str =
do prims <- getPrimMap
return (P.EVar (lookupPrimDecl (packIdent str) prims))
desugarLiteral :: Bool -> P.Literal -> InferM (P.Expr Name)
desugarLiteral fixDec lit =
do l <- curRange
demotePrim <- mkPrim "demote"
let named (x,y) = P.NamedInst
P.Named { name = Located l (packIdent x), value = P.TNum y }
demote fs = P.EAppT demotePrim (map named fs)
return $ case lit of
P.ECNum num info ->
demote $ [ ("val", num) ] ++ case info of
P.BinLit n -> [ ("bits", 1 * toInteger n) ]
P.OctLit n -> [ ("bits", 3 * toInteger n) ]
P.HexLit n -> [ ("bits", 4 * toInteger n) ]
P.CharLit -> [ ("bits", 8 :: Integer) ]
P.DecLit
| fixDec -> if num == 0
then [ ("bits", 0)]
else case genLog num 2 of
Just (x,_) -> [ ("bits", x + 1) ]
_ -> []
| otherwise -> [ ]
P.PolyLit _n -> [ ]
P.ECString s ->
P.ETyped (P.EList [ P.ELit (P.ECNum (fromIntegral (fromEnum c))
P.CharLit) | c <- s ])
(P.TSeq P.TWild (P.TSeq (P.TNum 8) P.TBit))
-- | Infer the type of an expression with an explicit instantiation.
appTys :: P.Expr Name -> [Located (Maybe Ident,Type)] -> Type -> InferM Expr
appTys expr ts tGoal =
case expr of
P.EVar x ->
do res <- lookupVar x
(e',t) <- case res of
ExtVar s -> instantiateWith (EVar x) s ts
CurSCC e t -> instantiateWith e (Forall [] [] t) ts
checkHasType e' t tGoal
P.ELit l -> do e <- desugarLiteral False l
appTys e ts tGoal
P.EAppT e fs ->
do ps <- mapM inferTyParam fs
appTys e (ps ++ ts) tGoal
-- Here is an example of why this might be useful:
-- f ` { x = T } where type T = ...
P.EWhere e ds ->
inferDs ds $ \ds1 -> do e1 <- appTys e ts tGoal
return (EWhere e1 ds1)
-- XXX: Is there a scoping issue here? I think not, but check.
P.ELocated e r ->
inRange r (appTys e ts tGoal)
P.ETuple {} -> mono
P.ERecord {} -> mono
P.ESel {} -> mono
P.EList {} -> mono
P.EFromTo {} -> mono
P.EInfFrom {} -> mono
P.EComp {} -> mono
P.EApp {} -> mono
P.EIf {} -> mono
P.ETyped {} -> mono
P.ETypeVal {} -> mono
P.EFun {} -> mono
P.EParens e -> appTys e ts tGoal
P.EInfix a op _ b -> appTys (P.EVar (thing op) `P.EApp` a `P.EApp` b) ts tGoal
where mono = do e' <- checkE expr tGoal
(ie,t) <- instantiateWith e' (Forall [] [] tGoal) ts
-- XXX seems weird to need to do this, as t should be the same
-- as tGoal
checkHasType ie t tGoal
inferTyParam :: P.TypeInst Name -> InferM (Located (Maybe Ident, Type))
inferTyParam (P.NamedInst param) =
do let loc = srcRange (P.name param)
t <- inRange loc $ checkType (P.value param) Nothing
return $ Located loc (Just (thing (P.name param)), t)
inferTyParam (P.PosInst param) =
do t <- checkType param Nothing
rng <- case getLoc param of
Nothing -> curRange
Just r -> return r
return Located { srcRange = rng, thing = (Nothing, t) }
checkTypeOfKind :: P.Type Name -> Kind -> InferM Type
checkTypeOfKind ty k = checkType ty (Just k)
-- | We use this when we want to ensure that the expr has exactly
-- (syntactically) the given type.
inferE :: Doc -> P.Expr Name -> InferM (Expr, Type)
inferE desc expr =
do t <- newType desc KType
e1 <- checkE expr t
return (e1,t)
-- | Infer the type of an expression, and translate it to a fully elaborated
-- core term.
checkE :: P.Expr Name -> Type -> InferM Expr
checkE expr tGoal =
case expr of
P.EVar x ->
do res <- lookupVar x
(e',t) <- case res of
ExtVar s -> instantiateWith (EVar x) s []
CurSCC e t -> return (e, t)
checkHasType e' t tGoal
P.ELit l -> (`checkE` tGoal) =<< desugarLiteral False l
P.ETuple es ->
do etys <- expectTuple (length es) tGoal
es' <- zipWithM checkE es etys
return (ETuple es')
P.ERecord fs ->
do (ns,es,ts) <- unzip3 `fmap` expectRec fs tGoal
es' <- zipWithM checkE es ts
return (ERec (zip ns es'))
P.ESel e l ->
do let src = case l of
RecordSel _ _ -> text "type of record"
TupleSel _ _ -> text "type of tuple"
ListSel _ _ -> text "type of sequence"
(e',t) <- inferE src e
f <- newHasGoal l t tGoal
return (f e')
P.EList [] ->
do (len,a) <- expectSeq tGoal
expectFin 0 len
return (EList [] a)
P.EList es ->
do (len,a) <- expectSeq tGoal
expectFin (length es) len
es' <- mapM (`checkE` a) es
return (EList es' a)
P.EFromTo t1 Nothing Nothing ->
do rng <- curRange
bit <- newType (text "bit-width of enumeration sequnce") KNum
fstT <- checkTypeOfKind t1 KNum
let totLen = tNum (2::Int) .^. bit
lstT = totLen .-. tNum (1::Int)
fromToPrim <- mkPrim "fromTo"
appTys fromToPrim
[ Located rng (Just (packIdent x), y)
| (x,y) <- [ ("first",fstT), ("last", lstT), ("bits", bit) ]
] tGoal
P.EFromTo t1 mbt2 mbt3 ->
do l <- curRange
let (c,fs) =
case (mbt2, mbt3) of
(Nothing, Nothing) -> tcPanic "checkE"
[ "EFromTo _ Nothing Nothing" ]
(Just t2, Nothing) ->
("fromThen", [ ("next", t2) ])
(Nothing, Just t3) ->
("fromTo", [ ("last", t3) ])
(Just t2, Just t3) ->
("fromThenTo", [ ("next",t2), ("last",t3) ])
prim <- mkPrim c
let e' = P.EAppT prim
[ P.NamedInst P.Named { name = Located l (packIdent x), value = y }
| (x,y) <- ("first",t1) : fs
]
checkE e' tGoal
P.EInfFrom e1 Nothing ->
do prim <- mkPrim "infFrom"
checkE (P.EApp prim e1) tGoal
P.EInfFrom e1 (Just e2) ->
do prim <- mkPrim "infFromThen"
checkE (P.EApp (P.EApp prim e1) e2) tGoal
P.EComp e mss ->
do (mss', dss, ts) <- unzip3 `fmap` zipWithM inferCArm [ 1 .. ] mss
(len,a)<- expectSeq tGoal
newGoals CtComprehension =<< unify len =<< smallest ts
ds <- combineMaps dss
e' <- withMonoTypes ds (checkE e a)
return (EComp tGoal e' mss')
P.EAppT e fs ->
do ts <- mapM inferTyParam fs
appTys e ts tGoal
P.EApp fun@(dropLoc -> P.EApp (dropLoc -> P.EVar c) _)
arg@(dropLoc -> P.ELit l)
| Just n <- asPrim c
, n `elem` map packIdent [ "<<", ">>", "<<<", ">>>" , "@", "!" ] ->
do newArg <- do l1 <- desugarLiteral True l
return $ case arg of
P.ELocated _ pos -> P.ELocated l1 pos
_ -> l1
checkE (P.EApp fun newArg) tGoal
P.EApp e1 e2 ->
do t1 <- newType (text "argument to function") KType
e1' <- checkE e1 (tFun t1 tGoal)
e2' <- checkE e2 t1
return (EApp e1' e2')
P.EIf e1 e2 e3 ->
do e1' <- checkE e1 tBit
e2' <- checkE e2 tGoal
e3' <- checkE e3 tGoal
return (EIf e1' e2' e3')
P.EWhere e ds ->
inferDs ds $ \ds1 -> do e1 <- checkE e tGoal
return (EWhere e1 ds1)
P.ETyped e t ->
do tSig <- checkTypeOfKind t KType
e' <- checkE e tSig
checkHasType e' tSig tGoal
P.ETypeVal t ->
do l <- curRange
prim <- mkPrim "demote"
checkE (P.EAppT prim
[P.NamedInst
P.Named { name = Located l (packIdent "val"), value = t }]) tGoal
P.EFun ps e -> checkFun (text "anonymous function") ps e tGoal
P.ELocated e r -> inRange r (checkE e tGoal)
P.EInfix a op _ b -> checkE (P.EVar (thing op) `P.EApp` a `P.EApp` b) tGoal
P.EParens e -> checkE e tGoal
expectSeq :: Type -> InferM (Type,Type)
expectSeq ty =
case ty of
TUser _ _ ty' ->
expectSeq ty'
TCon (TC TCSeq) [a,b] ->
return (a,b)
TVar _ ->
do tys@(a,b) <- genTys
newGoals CtExactType =<< unify (tSeq a b) ty
return tys
_ ->
do tys@(a,b) <- genTys
recordError (TypeMismatch (tSeq a b) ty)
return tys
where
genTys =
do a <- newType (text "size of the sequence") KNum
b <- newType (text "type of sequence elements") KType
return (a,b)
expectTuple :: Int -> Type -> InferM [Type]
expectTuple n ty =
case ty of
TUser _ _ ty' ->
expectTuple n ty'
TCon (TC (TCTuple n')) tys | n == n' ->
return tys
TVar _ ->
do tys <- genTys
newGoals CtExactType =<< unify (tTuple tys) ty
return tys
_ ->
do tys <- genTys
recordError (TypeMismatch (tTuple tys) ty)
return tys
where
genTys =forM [ 0 .. n - 1 ] $ \ i ->
let desc = text "type of"
<+> ordinal i
<+> text "tuple field"
in newType desc KType
expectRec :: [P.Named a] -> Type -> InferM [(Ident,a,Type)]
expectRec fs ty =
case ty of
TUser _ _ ty' ->
expectRec fs ty'
TRec ls | Just tys <- mapM checkField ls ->
return tys
_ ->
do (tys,res) <- genTys
case ty of
TVar TVFree{} -> do ps <- unify (TRec tys) ty
newGoals CtExactType ps
_ -> recordError (TypeMismatch (TRec tys) ty)
return res
where
checkField (n,t) =
do f <- find (\f -> thing (P.name f) == n) fs
return (thing (P.name f), P.value f, t)
genTys =
do res <- forM fs $ \ f ->
do let field = thing (P.name f)
t <- newType (text "type of field" <+> quotes (pp field)) KType
return (field, P.value f, t)
let (ls,_,ts) = unzip3 res
return (zip ls ts, res)
expectFin :: Int -> Type -> InferM ()
expectFin n ty =
case ty of
TUser _ _ ty' ->
expectFin n ty'
TCon (TC (TCNum n')) [] | toInteger n == n' ->
return ()
_ ->
do newGoals CtExactType =<< unify (tNum n) ty
expectFun :: Int -> Type -> InferM ([Type],Type)
expectFun = go []
where
go tys arity ty
| arity > 0 =
case ty of
TUser _ _ ty' ->
go tys arity ty'
TCon (TC TCFun) [a,b] ->
go (a:tys) (arity - 1) b
_ ->
do args <- genArgs arity
res <- newType (text "result of function") KType
case ty of
TVar TVFree{} -> do ps <- unify (foldr tFun res args) ty
newGoals CtExactType ps
_ -> recordError (TypeMismatch (foldr tFun res args) ty)
return (reverse tys ++ args, res)
| otherwise =
return (reverse tys, ty)
genArgs arity = forM [ 1 .. arity ] $ \ ix ->
newType (text "argument" <+> ordinal ix) KType
checkHasType :: Expr -> Type -> Type -> InferM Expr
checkHasType e inferredType givenType =
do ps <- unify givenType inferredType
case ps of
[] -> return e
_ -> newGoals CtExactType ps >> return (ECast e givenType)
checkFun :: Doc -> [P.Pattern Name] -> P.Expr Name -> Type -> InferM Expr
checkFun _ [] e tGoal = checkE e tGoal
checkFun desc ps e tGoal =
inNewScope $
do let descs = [ text "type of" <+> ordinal n <+> text "argument"
<+> text "of" <+> desc | n <- [ 1 :: Int .. ] ]
(tys,tRes) <- expectFun (length ps) tGoal
largs <- sequence (zipWith3 checkP descs ps tys)
let ds = Map.fromList [ (thing x, x { thing = t }) | (x,t) <- zip largs tys ]
e1 <- withMonoTypes ds (checkE e tRes)
let args = [ (thing x, t) | (x,t) <- zip largs tys ]
return (foldr (\(x,t) b -> EAbs x t b) e1 args)
{-| The type the is the smallest of all -}
smallest :: [Type] -> InferM Type
smallest [] = newType (text "length of list comprehension") KNum
smallest [t] = return t
smallest ts = do a <- newType (text "length of list comprehension") KNum
newGoals CtComprehension [ a =#= foldr1 tMin ts ]
return a
checkP :: Doc -> P.Pattern Name -> Type -> InferM (Located Name)
checkP desc p tGoal =
do (x, t) <- inferP desc p
ps <- unify tGoal (thing t)
let rng = fromMaybe emptyRange $ getLoc p
let mkErr = recordError . UnsolvedGoal False . Goal (CtPattern desc) rng
mapM_ mkErr ps
return (Located (srcRange t) x)
{-| Infer the type of a pattern. Assumes that the pattern will be just
a variable. -}
inferP :: Doc -> P.Pattern Name -> InferM (Name, Located Type)
inferP desc pat =
case pat of
P.PVar x0 ->
do a <- newType desc KType
return (thing x0, x0 { thing = a })
P.PTyped p t ->
do tSig <- checkTypeOfKind t KType
ln <- checkP desc p tSig
return (thing ln, ln { thing = tSig })
_ -> tcPanic "inferP" [ "Unexpected pattern:", show pat ]
-- | Infer the type of one match in a list comprehension.
inferMatch :: P.Match Name -> InferM (Match, Name, Located Type, Type)
inferMatch (P.Match p e) =
do (x,t) <- inferP (text "XXX:MATCH") p
n <- newType (text "sequence length of comprehension match") KNum
e' <- checkE e (tSeq n (thing t))
return (From x (thing t) e', x, t, n)
inferMatch (P.MatchLet b)
| P.bMono b =
do a <- newType (text "`let` binding in comprehension") KType
b1 <- checkMonoB b a
return (Let b1, dName b1, Located (srcRange (P.bName b)) a, tNum (1::Int))
| otherwise = tcPanic "inferMatch"
[ "Unexpected polymorphic match let:", show b ]
-- | Infer the type of one arm of a list comprehension.
inferCArm :: Int -> [P.Match Name] -> InferM
( [Match]
, Map Name (Located Type)-- defined vars
, Type -- length of sequence
)
inferCArm _ [] = do n <- newType (text "lenght of empty comprehension") KNum
-- shouldn't really happen
return ([], Map.empty, n)
inferCArm _ [m] =
do (m1, x, t, n) <- inferMatch m
return ([m1], Map.singleton x t, n)
inferCArm armNum (m : ms) =
do (m1, x, t, n) <- inferMatch m
(ms', ds, n') <- withMonoType (x,t) (inferCArm armNum ms)
-- XXX: Well, this is just the lenght of this sub-sequence
let src = text "length of" <+> ordinal armNum <+>
text "arm of list comprehension"
sz <- newType src KNum
newGoals CtComprehension [ sz =#= (n .*. n') ]
return (m1 : ms', Map.insertWith (\_ old -> old) x t ds, sz)
-- | @inferBinds isTopLevel isRec binds@ performs inference for a
-- strongly-connected component of 'P.Bind's. If @isTopLevel@ is true,
-- any bindings without type signatures will be generalized. If it is
-- false, and the mono-binds flag is enabled, no bindings without type
-- signatures will be generalized, but bindings with signatures will
-- be unaffected.
inferBinds :: Bool -> Bool -> [P.Bind Name] -> InferM [Decl]
inferBinds isTopLevel isRec binds =
mdo let dExpr (DExpr e) = e
dExpr DPrim = panic "[TypeCheck]" [ "primitive in a recursive group" ]
exprMap = Map.fromList [ (x,inst (EVar x) (dExpr (dDefinition b)))
| b <- genBs, let x = dName b ] -- REC.
inst e (ETAbs x e1) = inst (ETApp e (TVar (tpVar x))) e1
inst e (EProofAbs _ e1) = inst (EProofApp e) e1
inst e _ = e
-- when mono-binds is enabled, and we're not checking top-level
-- declarations, mark all bindings lacking signatures as monomorphic
monoBinds <- getMonoBinds
let binds' | monoBinds && not isTopLevel = sigs ++ monos
| otherwise = binds
(sigs,noSigs) = partition (isJust . P.bSignature) binds
monos = [ b { P.bMono = True } | b <- noSigs ]
((doneBs, genCandidates), cs) <-
collectGoals $
{- Guess type is here, because while we check user supplied signatures
we may generate additional constraints. For example, `x - y` would
generate an additional constraint `x >= y`. -}
do (newEnv,todos) <- unzip `fmap` mapM (guessType exprMap) binds'
let extEnv = if isRec then withVarTypes newEnv else id
extEnv $
do let (sigsAndMonos,noSigGen) = partitionEithers todos
genCs <- sequence noSigGen
done <- sequence sigsAndMonos
simplifyAllConstraints
return (done, genCs)
genBs <- generalize genCandidates cs -- RECURSION
return (doneBs ++ genBs)
{- | Come up with a type for recursive calls to a function, and decide
how we are going to be checking the binding.
Returns: (Name, type or schema, computation to check binding)
The `exprMap` is a thunk where we can lookup the final expressions
and we should be careful not to force it.
-}
guessType :: Map Name Expr -> P.Bind Name ->
InferM ( (Name, VarType)
, Either (InferM Decl) -- no generalization
(InferM Decl) -- generalize these
)
guessType exprMap b@(P.Bind { .. }) =
case bSignature of
Just s ->
do s1 <- checkSchema s
return ((name, ExtVar (fst s1)), Left (checkSigB b s1))
Nothing
| bMono ->
do t <- newType (text "defintion of" <+> quotes (pp name)) KType
let schema = Forall [] [] t
return ((name, ExtVar schema), Left (checkMonoB b t))
| otherwise ->
do t <- newType (text "definition of" <+> quotes (pp name)) KType
let noWay = tcPanic "guessType" [ "Missing expression for:" ,
show name ]
expr = Map.findWithDefault noWay name exprMap
return ((name, CurSCC expr t), Right (checkMonoB b t))
where
name = thing bName
-- | Try to evaluate the inferred type in a binding.
simpBind :: Decl -> Decl
simpBind d =
case dSignature d of
Forall as qs t ->
case simpTypeMaybe t of
Nothing -> d
Just t1 -> d { dSignature = Forall as qs t1
, dDefinition = case dDefinition d of
DPrim -> DPrim
DExpr e -> DExpr (castUnder t1 e)
}
where
-- Assumes the quantifiers match
castUnder t (ETAbs a e) = ETAbs a (castUnder t e)
castUnder t (EProofAbs p e) = EProofAbs p (castUnder t e)
castUnder t e = ECast e t
-- | The inputs should be declarations with monomorphic types
-- (i.e., of the form `Forall [] [] t`).
generalize :: [Decl] -> [Goal] -> InferM [Decl]
{- This may happen because we have monomorphic bindings.
In this case we may get some goal, due to the monomorphic bindings,
but the group of components is empty. -}
generalize [] gs0 =
do addGoals gs0
return []
generalize bs0 gs0 =
do gs <- forM gs0 $ \g -> applySubst g
-- XXX: Why would these bindings have signatures??
bs1 <- forM bs0 $ \b -> do s <- applySubst (dSignature b)
return b { dSignature = s }
let bs = map simpBind bs1
let goalFVS g = Set.filter isFreeTV $ fvs $ goal g
inGoals = Set.unions $ map goalFVS gs
inSigs = Set.filter isFreeTV $ fvs $ map dSignature bs
candidates = Set.union inGoals inSigs
asmpVs <- varsWithAsmps
let gen0 = Set.difference candidates asmpVs
stays g = any (`Set.member` gen0) $ Set.toList $ goalFVS g
(here0,later) = partition stays gs
-- Figure out what might be ambigious
let (maybeAmbig, ambig) = partition ((KNum ==) . kindOf)
$ Set.toList
$ Set.difference gen0 inSigs
when (not (null ambig)) $ recordError $ AmbiguousType $ map dName bs
solver <- getSolver
(as0,here1,defSu,ws) <- io $ improveByDefaultingWith solver maybeAmbig here0
mapM_ recordWarning ws
let here = map goal here1
let as = as0 ++ Set.toList (Set.difference inSigs asmpVs)
asPs = [ TParam { tpUnique = x, tpKind = k, tpName = Nothing }
| TVFree x k _ _ <- as ]
totSu <- getSubst
let
su = listSubst (zip as (map (TVar . tpVar) asPs)) @@ defSu @@ totSu
qs = map (apSubst su) here
genE e = foldr ETAbs (foldr EProofAbs (apSubst su e) qs) asPs
genB d = d { dDefinition = case dDefinition d of
DExpr e -> DExpr (genE e)
DPrim -> DPrim
, dSignature = Forall asPs qs
$ apSubst su $ sType $ dSignature d
}
addGoals later
return (map (simpBind . genB) bs)
checkMonoB :: P.Bind Name -> Type -> InferM Decl
checkMonoB b t =
inRangeMb (getLoc b) $
case thing (P.bDef b) of
P.DPrim ->
return Decl { dName = thing (P.bName b)
, dSignature = Forall [] [] t
, dDefinition = DPrim
, dPragmas = P.bPragmas b
, dInfix = P.bInfix b
, dFixity = P.bFixity b
, dDoc = P.bDoc b
}
P.DExpr e ->
do e1 <- checkFun (pp (thing (P.bName b))) (P.bParams b) e t
let f = thing (P.bName b)
return Decl { dName = f
, dSignature = Forall [] [] t
, dDefinition = DExpr e1
, dPragmas = P.bPragmas b
, dInfix = P.bInfix b
, dFixity = P.bFixity b
, dDoc = P.bDoc b
}
-- XXX: Do we really need to do the defaulting business in two different places?
checkSigB :: P.Bind Name -> (Schema,[Goal]) -> InferM Decl
checkSigB b (Forall as asmps0 t0, validSchema) = case thing (P.bDef b) of
-- XXX what should we do with validSchema in this case?
P.DPrim ->
do return Decl { dName = thing (P.bName b)
, dSignature = Forall as asmps0 t0
, dDefinition = DPrim
, dPragmas = P.bPragmas b
, dInfix = P.bInfix b
, dFixity = P.bFixity b
, dDoc = P.bDoc b
}
P.DExpr e0 ->
inRangeMb (getLoc b) $
withTParams as $
do (e1,cs0) <- collectGoals $
do e1 <- checkFun (pp (thing (P.bName b))) (P.bParams b) e0 t0
() <- simplifyAllConstraints -- XXX: using `asmps` also...
return e1
cs <- applySubst cs0
let letGo qs c = Set.null (qs `Set.intersection` fvs (goal c))
splitPreds qs n ps =
let (l,n1) = partition (letGo qs) ps
in if null n1
then (l,n)
else splitPreds (fvs (map goal n1) `Set.union` qs) (n1 ++ n) l
(later0,now) = splitPreds (Set.fromList (map tpVar as)) [] cs
asmps1 <- applySubst asmps0
defSu1 <- proveImplication (thing (P.bName b)) as asmps1 (validSchema ++ now)
let later = apSubst defSu1 later0
asmps = apSubst defSu1 asmps1
-- Now we check for any remaining variables that are not mentioned
-- in the environment. The plan is to try to default these to something
-- reasonable.
do let laterVs = fvs (map goal later)
asmpVs <- varsWithAsmps
let genVs = laterVs `Set.difference` asmpVs
(maybeAmbig,ambig) = partition ((== KNum) . kindOf)
(Set.toList genVs)
when (not (null ambig)) $ recordError
$ AmbiguousType [ thing (P.bName b) ]
solver <- getSolver
(_,_,defSu2,ws) <- io $ improveByDefaultingWith solver maybeAmbig later
mapM_ recordWarning ws
extendSubst defSu2
addGoals later
su <- getSubst
let su' = defSu1 @@ su
t = apSubst su' t0
e2 = apSubst su' e1
return Decl
{ dName = thing (P.bName b)
, dSignature = Forall as asmps t
, dDefinition = DExpr (foldr ETAbs (foldr EProofAbs e2 asmps) as)
, dPragmas = P.bPragmas b
, dInfix = P.bInfix b
, dFixity = P.bFixity b
, dDoc = P.bDoc b
}
inferDs :: FromDecl d => [d] -> ([DeclGroup] -> InferM a) -> InferM a
inferDs ds continue = checkTyDecls =<< orderTyDecls (mapMaybe toTyDecl ds)
where
isTopLevel = isTopDecl (head ds)
checkTyDecls (TS t : ts) =
do t1 <- checkTySyn t
withTySyn t1 (checkTyDecls ts)
checkTyDecls (NT t : ts) =
do t1 <- checkNewtype t
withNewtype t1 (checkTyDecls ts)
-- We checked all type synonyms, now continue with value-level definitions:
checkTyDecls [] = checkBinds [] $ orderBinds $ mapMaybe toBind ds
checkBinds decls (CyclicSCC bs : more) =
do bs1 <- inferBinds isTopLevel True bs
foldr (\b m -> withVar (dName b) (dSignature b) m)
(checkBinds (Recursive bs1 : decls) more)
bs1
checkBinds decls (AcyclicSCC c : more) =
do [b] <- inferBinds isTopLevel False [c]
withVar (dName b) (dSignature b) $
checkBinds (NonRecursive b : decls) more
-- We are done with all value-level definitions.
-- Now continue with anything that's in scope of the declarations.
checkBinds decls [] = continue (reverse decls)
tcPanic :: String -> [String] -> a
tcPanic l msg = panic ("[TypeCheck] " ++ l) msg
cryptol-2.4.0/src/Cryptol/TypeCheck/InferTypes.hs 0000644 0000000 0000000 00000047071 12737220176 020145 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- This module contains types used during type inference.
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Cryptol.TypeCheck.InferTypes where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst
import Cryptol.TypeCheck.TypeMap
import Cryptol.Parser.Position
import qualified Cryptol.Parser.AST as P
import Cryptol.Utils.PP
import Cryptol.ModuleSystem.Name (asPrim,nameLoc)
import Cryptol.TypeCheck.PP
import Cryptol.Utils.Ident (Ident,identText)
import Cryptol.Utils.Panic(panic)
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.IntMap as IntMap
import GHC.Generics (Generic)
import Control.DeepSeq
data SolverConfig = SolverConfig
{ solverPath :: FilePath -- ^ The SMT solver to invoke
, solverArgs :: [String] -- ^ Additional arguments to pass to the solver
, solverVerbose :: Int -- ^ How verbose to be when type-checking
} deriving (Show, Generic, NFData)
-- | The types of variables in the environment.
data VarType = ExtVar Schema -- ^ Known type
| CurSCC Expr Type -- ^ Part of current SCC
newtype Goals = Goals (TypeMap Goal)
deriving (Show)
emptyGoals :: Goals
emptyGoals = Goals emptyTM
nullGoals :: Goals -> Bool
nullGoals (Goals tm) = nullTM tm
fromGoals :: Goals -> [Goal]
fromGoals (Goals tm) = membersTM tm
insertGoal :: Goal -> Goals -> Goals
insertGoal g (Goals tm) = Goals (insertTM (goal g) g tm)
-- | Something that we need to find evidence for.
data Goal = Goal
{ goalSource :: ConstraintSource -- ^ What it is about
, goalRange :: Range -- ^ Part of source code that caused goal
, goal :: Prop -- ^ What needs to be proved
} deriving (Show, Generic, NFData)
data HasGoal = HasGoal
{ hasName :: !Int
, hasGoal :: Goal
} deriving Show
-- | Delayed implication constraints, arising from user-specified type sigs.
data DelayedCt = DelayedCt
{ dctSource :: Name -- ^ Signature that gave rise to this constraint
, dctForall :: [TParam]
, dctAsmps :: [Prop]
, dctGoals :: [Goal]
} deriving (Show, Generic, NFData)
data Solved = Solved (Maybe Subst) [Goal] -- ^ Solved, assuming the sub-goals.
| Unsolved -- ^ We could not solve the goal.
| Unsolvable -- ^ The goal can never be solved.
deriving (Show)
data Warning = DefaultingKind (P.TParam Name) P.Kind
| DefaultingWildType P.Kind
| DefaultingTo Doc Type
deriving (Show, Generic, NFData)
-- | Various errors that might happen during type checking/inference
data Error = ErrorMsg Doc
-- ^ Just say this
| KindMismatch Kind Kind
-- ^ Expected kind, inferred kind
| TooManyTypeParams Int Kind
-- ^ Number of extra parameters, kind of result
-- (which should not be of the form @_ -> _@)
| TooManyTySynParams Name Int
-- ^ Type-synonym, number of extra params
| TooFewTySynParams Name Int
-- ^ Type-synonym, number of missing params
| RepeatedTyParams [P.TParam Name]
-- ^ Type parameters with the same name (in definition)
| RepeatedDefinitions Name [Range]
-- ^ Multiple definitions for the same name
| RecursiveTypeDecls [Name]
-- ^ The type synonym declarations are recursive
| UndefinedTypeSynonym Name
-- ^ Use of a type synonym that was not defined
| UndefinedVariable Name
-- ^ Use of a variable that was not defined
| UndefinedTypeParam (Located Ident)
-- ^ Attempt to explicitly instantiate a non-existent param.
| MultipleTypeParamDefs Ident [Range]
-- ^ Multiple definitions for the same type parameter
| TypeMismatch Type Type
-- ^ Expected type, inferred type
| RecursiveType Type Type
-- ^ Unification results in a recursive type
| UnsolvedGoal Bool Goal
-- ^ A constraint that we could not solve
-- The boolean indicates if we know that this constraint
-- is impossible.
| UnsolvedDelayedCt DelayedCt
-- ^ A constraint (with context) that we could not solve
| UnexpectedTypeWildCard
-- ^ Type wild cards are not allowed in this context
-- (e.g., definitions of type synonyms).
| TypeVariableEscaped Type [TVar]
-- ^ Unification variable depends on quantified variables
-- that are not in scope.
| NotForAll TVar Type
-- ^ Quantified type variables (of kind *) need to
-- match the given type, so it does not work for all types.
| UnusableFunction Name [Prop]
-- ^ The given constraints causes the signature of the
-- function to be not-satisfiable.
| TooManyPositionalTypeParams
-- ^ Too many positional type arguments, in an explicit
-- type instantiation
| CannotMixPositionalAndNamedTypeParams
| AmbiguousType [Name]
deriving (Show, Generic, NFData)
-- | Information about how a constraint came to be, used in error reporting.
data ConstraintSource
= CtComprehension -- ^ Computing shape of list comprehension
| CtSplitPat -- ^ Use of a split pattern
| CtTypeSig -- ^ A type signature in a pattern or expression
| CtInst Expr -- ^ Instantiation of this expression
| CtSelector
| CtExactType
| CtEnumeration
| CtDefaulting -- ^ Just defaulting on the command line
| CtPartialTypeFun TyFunName -- ^ Use of a partial type function.
| CtImprovement
| CtPattern Doc -- ^ Constraints arising from type-checking patterns
deriving (Show, Generic, NFData)
data TyFunName = UserTyFun Name | BuiltInTyFun TFun
deriving (Show, Generic, NFData)
instance PP TyFunName where
ppPrec c (UserTyFun x) = ppPrec c x
ppPrec c (BuiltInTyFun x) = ppPrec c x
instance TVars ConstraintSource where
apSubst su src =
case src of
CtComprehension -> src
CtSplitPat -> src
CtTypeSig -> src
CtInst e -> CtInst (apSubst su e)
CtSelector -> src
CtExactType -> src
CtEnumeration -> src
CtDefaulting -> src
CtPartialTypeFun _ -> src
CtImprovement -> src
CtPattern _ -> src
instance TVars Warning where
apSubst su warn =
case warn of
DefaultingKind {} -> warn
DefaultingWildType {} -> warn
DefaultingTo d ty -> DefaultingTo d (apSubst su ty)
instance FVS Warning where
fvs warn =
case warn of
DefaultingKind {} -> Set.empty
DefaultingWildType {} -> Set.empty
DefaultingTo _ ty -> fvs ty
instance TVars Error where
apSubst su err =
case err of
ErrorMsg _ -> err
KindMismatch {} -> err
TooManyTypeParams {} -> err
TooManyTySynParams {} -> err
TooFewTySynParams {} -> err
RepeatedTyParams {} -> err
RepeatedDefinitions {} -> err
RecursiveTypeDecls {} -> err
UndefinedTypeSynonym {} -> err
UndefinedVariable {} -> err
UndefinedTypeParam {} -> err
MultipleTypeParamDefs {} -> err
TypeMismatch t1 t2 -> TypeMismatch (apSubst su t1) (apSubst su t2)
RecursiveType t1 t2 -> RecursiveType (apSubst su t1) (apSubst su t2)
UnsolvedGoal x g -> UnsolvedGoal x (apSubst su g)
UnsolvedDelayedCt g -> UnsolvedDelayedCt (apSubst su g)
UnexpectedTypeWildCard -> err
TypeVariableEscaped t xs -> TypeVariableEscaped (apSubst su t) xs
NotForAll x t -> NotForAll x (apSubst su t)
UnusableFunction f ps -> UnusableFunction f (apSubst su ps)
TooManyPositionalTypeParams -> err
CannotMixPositionalAndNamedTypeParams -> err
AmbiguousType _ -> err
instance FVS Error where
fvs err =
case err of
ErrorMsg {} -> Set.empty
KindMismatch {} -> Set.empty
TooManyTypeParams {} -> Set.empty
TooManyTySynParams {} -> Set.empty
TooFewTySynParams {} -> Set.empty
RepeatedTyParams {} -> Set.empty
RepeatedDefinitions {} -> Set.empty
RecursiveTypeDecls {} -> Set.empty
UndefinedTypeSynonym {} -> Set.empty
UndefinedVariable {} -> Set.empty
UndefinedTypeParam {} -> Set.empty
MultipleTypeParamDefs {} -> Set.empty
TypeMismatch t1 t2 -> fvs (t1,t2)
RecursiveType t1 t2 -> fvs (t1,t2)
UnsolvedGoal _ g -> fvs g
UnsolvedDelayedCt g -> fvs g
UnexpectedTypeWildCard -> Set.empty
TypeVariableEscaped t _ -> fvs t
NotForAll _ t -> fvs t
UnusableFunction _ p -> fvs p
TooManyPositionalTypeParams -> Set.empty
CannotMixPositionalAndNamedTypeParams -> Set.empty
AmbiguousType _ -> Set.empty
instance FVS Goal where
fvs g = fvs (goal g)
instance FVS DelayedCt where
fvs d = fvs (dctAsmps d, dctGoals d) `Set.difference`
Set.fromList (map tpVar (dctForall d))
-- This first applies the substitution to the keys of the goal map, then to the
-- values that remain, as applying the substitution to the keys will only ever
-- reduce the number of values that remain.
instance TVars Goals where
apSubst su (Goals goals) =
Goals (mapWithKeyTM setGoal (apSubstTypeMapKeys su goals))
where
-- as the key for the goal map is the same as the goal, and the substitution
-- has been applied to the key already, just replace the existing goal with
-- the key.
setGoal key g = g { goalSource = apSubst su (goalSource g)
, goal = key
}
instance TVars Goal where
apSubst su g = Goal { goalSource = apSubst su (goalSource g)
, goalRange = goalRange g
, goal = apSubst su (goal g)
}
instance TVars HasGoal where
apSubst su h = h { hasGoal = apSubst su (hasGoal h) }
instance TVars DelayedCt where
apSubst su g
| Set.null captured =
DelayedCt { dctSource = dctSource g
, dctForall = dctForall g
, dctAsmps = apSubst su1 (dctAsmps g)
, dctGoals = apSubst su1 (dctGoals g)
}
| otherwise = panic "Cryptol.TypeCheck.Subst.apSubst (DelayedCt)"
[ "Captured quantified variables:"
, "Substitution: " ++ show m1
, "Variables: " ++ show captured
, "Constraint: " ++ show g
]
where
used = fvs (dctAsmps g, map goal (dctGoals g)) `Set.difference`
Set.fromList (map tpVar (dctForall g))
m1 = Map.filterWithKey (\k _ -> k `Set.member` used) (suMap su)
su1 = S { suMap = m1, suDefaulting = suDefaulting su }
captured = Set.fromList (map tpVar (dctForall g)) `Set.intersection`
fvs (Map.elems m1)
-- | For use in error messages
cppKind :: Kind -> Doc
cppKind ki =
case ki of
KNum -> text "a numeric type"
KType -> text "a value type"
KProp -> text "a constraint"
_ -> pp ki
addTVarsDescs :: FVS t => NameMap -> t -> Doc -> Doc
addTVarsDescs nm t d
| Set.null vs = d
| otherwise = d $$ text "where" $$ vcat (map desc (Set.toList vs))
where
vs = Set.filter isFreeTV (fvs t)
desc v@(TVFree _ _ _ x) = ppWithNames nm v <+> text "is" <+> x
desc (TVBound {}) = empty
instance PP Warning where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP Error where
ppPrec = ppWithNamesPrec IntMap.empty
instance PP (WithNames Warning) where
ppPrec _ (WithNames warn names) =
addTVarsDescs names warn $
case warn of
DefaultingKind x k ->
text "Assuming " <+> pp x <+> text "to have" <+> P.cppKind k
DefaultingWildType k ->
text "Assuming _ to have" <+> P.cppKind k
DefaultingTo d ty ->
text "Defaulting" <+> d $$ text "to" <+> ppWithNames names ty
instance PP (WithNames Error) where
ppPrec _ (WithNames err names) =
addTVarsDescs names err $
case err of
ErrorMsg msg -> msg
RecursiveType t1 t2 ->
nested (text "Matching would result in an infinite type.")
(text "The type: " <+> ppWithNames names t1 $$
text "occurs in:" <+> ppWithNames names t2)
UnexpectedTypeWildCard ->
nested (text "Wild card types are not allowed in this context")
(text "(e.g., they cannot be used in type synonyms).")
KindMismatch k1 k2 ->
nested (text "Incorrect type form.")
(text "Expected:" <+> cppKind k1 $$
text "Inferred:" <+> cppKind k2)
TooManyTypeParams extra k ->
nested (text "Malformed type.")
(text "Kind" <+> quotes (pp k) <+> text "is not a function," $$
text "but it was applied to" <+> pl extra "parameter" <> text ".")
TooManyTySynParams t extra ->
nested (text "Malformed type.")
(text "Type synonym" <+> nm t <+> text "was applied to" <+>
pl extra "extra parameter" <> text ".")
TooFewTySynParams t few ->
nested (text "Malformed type.")
(text "Type" <+> nm t <+> text "is missing" <+>
int few <+> text "parameters.")
RepeatedTyParams ps ->
nested (text "Different type parameters use the same name:")
(vmulti [ nm (P.tpName p) <+>
text "defined at" <+> mb (P.tpRange p) | p <- ps ] )
where mb Nothing = text "unknown location"
mb (Just x) = pp x
RepeatedDefinitions x ps ->
nested (text "Multiple definitions for the same name:")
(vmulti [ nm x <+> text "defined at" <+> pp p | p <- ps ])
RecursiveTypeDecls ts ->
nested (text "Recursive type declarations:")
(fsep $ punctuate comma $ map nm ts)
UndefinedTypeSynonym x ->
text "Type synonym" <+> nm x <+> text "is not defined."
UndefinedVariable x ->
text "Variable" <+> nm x <+> text "was not defined."
UndefinedTypeParam x ->
text "Type variable" <+> nm x <+> text "was not defined."
MultipleTypeParamDefs x ps ->
nested (text "Multiple definitions for the same type parameter"
<+> nm x <> text ":")
(vmulti [ text "defined at" <+> pp p | p <- ps ])
TypeMismatch t1 t2 ->
nested (text "Type mismatch:")
(text "Expected type:" <+> ppWithNames names t1 $$
text "Inferred type:" <+> ppWithNames names t2)
UnsolvedGoal imp g ->
nested (word <+> text "constraint:") (ppWithNames names g)
where word = if imp then text "Unsolvable" else text "Unsolved"
UnsolvedDelayedCt g ->
nested (text "Failed to validate user-specified signature.")
(ppWithNames names g)
TypeVariableEscaped t xs ->
nested (text "The type" <+> ppWithNames names t <+>
text "is not sufficiently polymorphic.")
(text "It cannot depend on quantified variables:" <+>
sep (punctuate comma (map (ppWithNames names) xs)))
NotForAll x t ->
nested (text "Inferred type is not sufficiently polymorphic.")
(text "Quantified variable:" <+> ppWithNames names x $$
text "cannot match type:" <+> ppWithNames names t)
UnusableFunction f ps ->
nested (text "The constraints in the type signature of"
<+> quotes (pp f) <+> text "are unsolvable.")
(text "Detected while analyzing constraints:"
$$ vcat (map (ppWithNames names) ps))
TooManyPositionalTypeParams ->
text "Too many positional type-parameters in explicit type application"
CannotMixPositionalAndNamedTypeParams ->
text "Named and positional type applications may not be mixed."
AmbiguousType xs ->
text "The inferred type for" <+> commaSep (map pp xs)
<+> text "is ambiguous."
where
nested x y = x $$ nest 2 y
pl 1 x = text "1" <+> text x
pl n x = text (show n) <+> text x <> text "s"
nm x = text "`" <> pp x <> text "`"
vmulti = vcat . multi
multi [] = []
multi [x] = [x <> text "."]
multi [x,y] = [x <> text ", and", y <> text "." ]
multi (x : xs) = x <> text "," : multi xs
instance PP ConstraintSource where
ppPrec _ src =
case src of
CtComprehension -> text "list comprehension"
CtSplitPat -> text "split (#) pattern"
CtTypeSig -> text "type signature"
CtInst e -> text "use of" <+> ppUse e
CtSelector -> text "use of selector"
CtExactType -> text "matching types"
CtEnumeration -> text "list enumeration"
CtDefaulting -> text "defaulting"
CtPartialTypeFun f -> text "use of partial type function" <+> pp f
CtImprovement -> text "examination of collected goals"
CtPattern desc -> text "checking a pattern:" <+> desc
ppUse :: Expr -> Doc
ppUse expr =
case expr of
EVar (asPrim -> Just prim)
| identText prim == "demote" -> text "literal or demoted expression"
| identText prim == "infFrom" -> text "infinite enumeration"
| identText prim == "infFromThen" -> text "infinite enumeration (with step)"
| identText prim == "fromThen" -> text "finite enumeration"
| identText prim == "fromTo" -> text "finite enumeration"
| identText prim == "fromThenTo" -> text "finite enumeration"
_ -> text "expression" <+> pp expr
instance PP (WithNames Goal) where
ppPrec _ (WithNames g names) =
(ppWithNames names (goal g)) $$
nest 2 (text "arising from" $$
pp (goalSource g) $$
text "at" <+> pp (goalRange g))
instance PP (WithNames DelayedCt) where
ppPrec _ (WithNames d names) =
sig $$ nest 2 (vars $$ asmps $$ vcat (map (ppWithNames ns1) (dctGoals d)))
where
sig = text "In the definition of" <+> quotes (pp name) <>
comma <+> text "at" <+> pp (nameLoc name) <> colon
name = dctSource d
vars = case dctForall d of
[] -> empty
xs -> text "for any type" <+>
fsep (punctuate comma (map (ppWithNames ns1 ) xs))
asmps = case dctAsmps d of
[] -> empty
xs -> nest 2 (vcat (map (ppWithNames ns1) xs)) $$ text "=>"
ns1 = addTNames (dctForall d) names
instance PP Solved where
ppPrec _ res =
case res of
Solved mb gs -> text "solved" $$ nest 2 (suDoc $$ vcat (map (pp . goal) gs))
where suDoc = maybe empty pp mb
Unsolved -> text "unsolved"
Unsolvable -> text "unsolvable"
cryptol-2.4.0/src/Cryptol/TypeCheck/Instantiate.hs 0000644 0000000 0000000 00000013274 12737220176 020336 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.TypeCheck.Instantiate (instantiateWith) where
import Cryptol.ModuleSystem.Name (nameIdent)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Monad
import Cryptol.TypeCheck.Subst (listSubst,apSubst)
import Cryptol.Parser.Position (Located(..))
import Cryptol.Utils.Ident (Ident)
import Cryptol.Utils.PP
import Data.Function (on)
import Data.List(sortBy, groupBy, find)
import Data.Maybe(mapMaybe,isJust)
import Data.Either(partitionEithers)
import MonadLib
instantiateWith :: Expr -> Schema -> [Located (Maybe Ident,Type)]
-> InferM (Expr,Type)
instantiateWith e s ts
| null named = instantiateWithPos e s positional
| null positional = instantiateWithNames e s named
| otherwise = do recordError CannotMixPositionalAndNamedTypeParams
instantiateWithNames e s named
where
(named,positional) = partitionEithers (map classify ts)
classify t = case thing t of
(Just n,ty) -> Left t { thing = (n,ty) }
(Nothing,ty) -> Right ty
instantiateWithPos :: Expr -> Schema -> [Type] -> InferM (Expr,Type)
instantiateWithPos e (Forall as ps t) ts =
do su <- makeSu (1::Int) [] as ts
doInst su e ps t
where
isNamed q = isJust (tpName q)
makeSu n su (q : qs) (ty : tys)
| not (isNamed q) = do r <- unnamed n q
makeSu (n+1) (r : su) qs (ty : tys)
| k1 == k2 = makeSu (n+1) ((tpVar q, ty) : su) qs tys
| otherwise = do recordError $ KindMismatch k1 k2
r <- unnamed n q
makeSu (n+1) (r : su) qs tys
where k1 = kindOf q
k2 = kindOf ty
makeSu _ su [] [] = return (reverse su)
makeSu n su (q : qs) [] = do r <- unnamed n q
makeSu (n+1) (r : su) qs []
makeSu _ su [] _ = do recordError TooManyPositionalTypeParams
return (reverse su)
unnamed n q = do r <- curRange
let src = ordinal n <+> text "type parameter"
$$ text "of" <+> ppUse e
$$ text "at" <+> pp r
ty <- newType src (kindOf q)
return (tpVar q, ty)
{- | Instantiate an expression of the given polymorphic type.
The arguments that are provided will be instantiated as requested,
the rest will be instantiated with fresh type variables.
Note that we assume that type parameters are not normalized.
Generally, the resulting expression will look something like this:
ECast (EProofApp (ETApp e t)) t1
where
- There will be one `ETApp t` for each insantiated type parameter;
- there will be one `EProofApp` for each constraint on the schema;
- there will be `ECast` if we had equality constraints from normalization.
-}
instantiateWithNames :: Expr -> Schema -> [Located (Ident,Type)]
-> InferM (Expr,Type)
instantiateWithNames e (Forall as ps t) xs =
do sequence_ repeatedParams
sequence_ undefParams
su' <- mapM paramInst as
doInst su' e ps t
where
-- Choose the type for type parameter `x`
paramInst x =
do let v = tpVar x
k = kindOf v
-- We just use nameIdent for comparison here, as all parameter names
-- should have a NameInfo of Parameter.
lkp name = find (\th -> fst (thing th) == nameIdent name) xs
src r = text "type parameter" <+> (case tpName x of
Just n -> quotes (pp n)
Nothing -> empty)
$$ text "of" <+> ppUse e
$$ text "at" <+> pp r
ty <- case lkp =<< tpName x of
Just lty
| k1 == k -> return ty
| otherwise -> do let r = srcRange lty
inRange r $ recordError (KindMismatch k k1)
newType (src r) k
where ty = snd (thing lty)
k1 = kindOf ty
Nothing -> do r <- curRange
newType (src r) k
return (v,ty)
-- Errors from multiple values for the same parameter.
repeatedParams = mapMaybe isRepeated
$ groupBy ((==) `on` pName)
$ sortBy (compare `on` pName) xs
isRepeated ys@(a : _ : _) = Just $ recordError
$ MultipleTypeParamDefs (fst (thing a))
(map srcRange ys)
isRepeated _ = Nothing
paramIdents = [ nameIdent n | Just n <- map tpName as ]
-- Errors from parameters that are defined, but do not exist in the schema.
undefParams = do x <- xs
let name = pName x
guard (name `notElem` paramIdents)
return $ inRange (srcRange x)
$ recordError
$ UndefinedTypeParam x { thing = name }
pName = fst . thing
doInst :: [(TVar, Type)] -> Expr -> [Prop] -> Type -> InferM (Expr,Type)
doInst su' e ps t =
do let su = listSubst su'
newGoals (CtInst e) (map (apSubst su) ps)
let t1 = apSubst su t
return ( addProofParams
$ addTyParams (map snd su') e
, t1)
where
-- Add type parameters
addTyParams ts e1 = foldl ETApp e1 ts
-- Add proof parameters (the proofs are ommited but we mark where they'd go)
addProofParams e1 = foldl (\e2 _ -> EProofApp e2) e1 ps
cryptol-2.4.0/src/Cryptol/TypeCheck/Kind.hs 0000644 0000000 0000000 00000026156 12737220176 016743 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Kind
( checkType
, checkSchema
, checkNewtype
, checkTySyn
) where
import qualified Cryptol.Parser.AST as P
import Cryptol.Parser.AST (Named(..))
import Cryptol.Parser.Position
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Monad hiding (withTParams)
import Cryptol.TypeCheck.Solve (simplifyAllConstraints
,wfTypeFunction)
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import qualified Data.Map as Map
import Data.List(sortBy,groupBy)
import Data.Maybe(fromMaybe)
import Data.Function(on)
import Control.Monad(unless,forM)
-- | Check a type signature.
checkSchema :: P.Schema Name -> InferM (Schema, [Goal])
checkSchema (P.Forall xs ps t mb) =
do ((xs1,(ps1,t1)), gs) <-
collectGoals $
rng $ withTParams True xs $
do ps1 <- mapM checkProp ps
t1 <- doCheckType t (Just KType)
return (ps1,t1)
return (Forall xs1 ps1 t1, gs)
where
rng = case mb of
Nothing -> id
Just r -> inRange r
-- | Check a type-synonym declaration.
checkTySyn :: P.TySyn Name -> InferM TySyn
checkTySyn (P.TySyn x as t) =
do ((as1,t1),gs) <- collectGoals
$ inRange (srcRange x)
$ do r <- withTParams False as (doCheckType t Nothing)
simplifyAllConstraints
return r
return TySyn { tsName = thing x
, tsParams = as1
, tsConstraints = map goal gs
, tsDef = t1
}
-- | Check a newtype declaration.
-- XXX: Do something with constraints.
checkNewtype :: P.Newtype Name -> InferM Newtype
checkNewtype (P.Newtype x as fs) =
do ((as1,fs1),gs) <- collectGoals $
inRange (srcRange x) $
do r <- withTParams False as $
forM fs $ \field ->
let n = name field
in kInRange (srcRange n) $
do t1 <- doCheckType (value field) (Just KType)
return (thing n, t1)
simplifyAllConstraints
return r
return Newtype { ntName = thing x
, ntParams = as1
, ntConstraints = map goal gs
, ntFields = fs1
}
checkType :: P.Type Name -> Maybe Kind -> InferM Type
checkType t k =
do (_, t1) <- withTParams True [] $ doCheckType t k
return t1
{- | Check something with type parameters.
When we check things with type parameters (i.e., type schemas, and type
synonym declarations) we do kind inference based only on the immediately
visible body. Type parameters that are not mentioned in the body are
defaulted to kind 'KNum'. If this is not the desired behavior, programmers
may add explicit kind annotations on the type parameters.
Here is an example of how this may show up:
> f : {n}. [8] -> [8]
> f x = x + `n
Note that @n@ does not appear in the body of the schema, so we will
default it to 'KNum', which is the correct thing in this case.
To use such a function, we'd have to provide an explicit type application:
> f `{n = 3}
There are two reasons for this choice:
1. It makes it possible to figure if something is correct without
having to look through arbitrary amounts of code.
2. It is a bit easier to implement, and it covers the large majority
of use cases, with a very small inconvenience (an explicit kind
annotation) in the rest.
-}
withTParams :: Bool -> [P.TParam Name] -> KindM a -> InferM ([TParam], a)
withTParams allowWildCards xs m =
mdo mapM_ recordError duplicates
(a, vars) <- runKindM allowWildCards (zip' xs ts) m
(as, ts) <- unzip `fmap` mapM (newTP vars) xs
return (as,a)
where
getKind vs tp =
case Map.lookup (P.tpName tp) vs of
Just k -> return k
Nothing -> do recordWarning (DefaultingKind tp P.KNum)
return KNum
newTP vs tp = do k <- getKind vs tp
n <- newTParam (Just (P.tpName tp)) k
return (n, TVar (tpVar n))
{- Note that we only zip based on the first argument.
This is needed to make the monadic recursion work correctly,
because the data dependency is only on the part that is known. -}
zip' [] _ = []
zip' (a:as) ~(t:ts) = (P.tpName a, fmap cvtK (P.tpKind a), t) : zip' as ts
cvtK P.KNum = KNum
cvtK P.KType = KType
duplicates = [ RepeatedTyParams ds
| ds@(_ : _ : _) <- groupBy ((==) `on` P.tpName)
$ sortBy (compare `on` P.tpName) xs ]
-- | Check an application of a type constant.
tcon :: TCon -- ^ Type constant being applied
-> [P.Type Name] -- ^ Type parameters
-> Maybe Kind -- ^ Expected kind
-> KindM Type -- ^ Resulting type
tcon tc ts0 k =
do (ts1,k1) <- appTy ts0 (kindOf tc)
checkKind (TCon tc ts1) k k1
-- | Check a use of a type-synonym, newtype, or scoped-type variable.
tySyn :: Bool -- ^ Should we check for scoped type vars.
-> Name -- ^ Name of type sysnonym
-> [P.Type Name]-- ^ Type synonym parameters
-> Maybe Kind -- ^ Expected kind
-> KindM Type -- ^ Resulting type
tySyn scoped x ts k =
do mb <- kLookupTSyn x
case mb of
Just (tysyn@(TySyn f as ps def)) ->
do (ts1,k1) <- appTy ts (kindOf tysyn)
ts2 <- checkParams as ts1
let su = zip as ts2
ps1 <- mapM (`kInstantiateT` su) ps
kNewGoals (CtPartialTypeFun (UserTyFun f)) ps1
t1 <- kInstantiateT def su
checkKind (TUser x ts1 t1) k k1
-- Maybe it is a newtype?
Nothing ->
do mbN <- kLookupNewtype x
case mbN of
Just nt ->
do let tc = newtypeTyCon nt
(ts1,_) <- appTy ts (kindOf tc)
ts2 <- checkParams (ntParams nt) ts1
return (TCon tc ts2)
-- Maybe it is a scoped type variable?
Nothing
| scoped -> kExistTVar x $ fromMaybe KNum k
| otherwise ->
do kRecordError $ UndefinedTypeSynonym x
kNewType (text "type synonym" <+> pp x) $ fromMaybe KNum k
where
checkParams as ts1
| paramHave == paramNeed = return ts1
| paramHave < paramNeed =
do kRecordError (TooFewTySynParams x (paramNeed-paramHave))
let src = text "missing prameter of" <+> pp x
fake <- mapM (kNewType src . kindOf . tpVar)
(drop paramHave as)
return (ts1 ++ fake)
| otherwise = do kRecordError (TooManyTySynParams x (paramHave-paramNeed))
return (take paramNeed ts1)
where paramHave = length ts1
paramNeed = length as
-- | Check a type-application.
appTy :: [P.Type Name] -- ^ Parameters to type function
-> Kind -- ^ Kind of type function
-> KindM ([Type], Kind) -- ^ Validated parameters, resulting kind
appTy [] k1 = return ([],k1)
appTy (t : ts) (k1 :-> k2) =
do t1 <- doCheckType t (Just k1)
(ts1,k) <- appTy ts k2
return (t1 : ts1, k)
appTy ts k1 =
do kRecordError (TooManyTypeParams (length ts) k1)
return ([], k1)
-- | Validate a parsed type.
doCheckType :: P.Type Name -- ^ Type that needs to be checked
-> Maybe Kind -- ^ Expected kind (if any)
-> KindM Type -- ^ Checked type
doCheckType ty k =
case ty of
P.TWild ->
do ok <- kWildOK
unless ok $ kRecordError UnexpectedTypeWildCard
theKind <- case k of
Just k1 -> return k1
Nothing -> do kRecordWarning (DefaultingWildType P.KNum)
return KNum
kNewType (text "wildcard") theKind
P.TFun t1 t2 -> tcon (TC TCFun) [t1,t2] k
P.TSeq t1 t2 -> tcon (TC TCSeq) [t1,t2] k
P.TBit -> tcon (TC TCBit) [] k
P.TNum n -> tcon (TC (TCNum n)) [] k
P.TChar n -> tcon (TC (TCNum $ fromIntegral $ fromEnum n)) [] k
P.TInf -> tcon (TC TCInf) [] k
P.TApp tf ts ->
do it <- tcon (TF tf) ts k
-- Now check for additional well-formedness
-- constraints.
case it of
TCon (TF f) ts' ->
case wfTypeFunction f ts' of
[] -> return ()
ps -> kNewGoals (CtPartialTypeFun (BuiltInTyFun f)) ps
_ -> return ()
return it
P.TTuple ts -> tcon (TC (TCTuple (length ts))) ts k
P.TRecord fs -> do t1 <- TRec `fmap` mapM checkF fs
checkKind t1 k KType
P.TLocated t r1 -> kInRange r1 $ doCheckType t k
P.TUser x [] -> checkTyThing x k
P.TUser x ts -> tySyn False x ts k
P.TParens t -> doCheckType t k
P.TInfix{} -> panic "KindCheck"
[ "TInfix not removed by the renamer", show ty ]
where
checkF f = do t <- kInRange (srcRange (name f))
$ doCheckType (value f) (Just KType)
return (thing (name f), t)
-- | Check a type-variable or type-synonym.
checkTyThing :: Name -- ^ Name of thing that needs checking
-> Maybe Kind -- ^ Expected kind
-> KindM Type
checkTyThing x k =
do it <- kLookupTyVar x
case it of
Just (TLocalVar t mbk) ->
case k of
Nothing -> return t
Just k1 ->
case mbk of
Nothing -> kSetKind x k1 >> return t
Just k2 -> checkKind t k k2
Just (TOuterVar t) -> checkKind t k (kindOf t)
Nothing -> tySyn True x [] k
-- | Validate a parsed proposition.
checkProp :: P.Prop Name -- ^ Proposition that need to be checked
-> KindM Type -- ^ Checked representation
checkProp prop =
case prop of
P.CFin t1 -> tcon (PC PFin) [t1] (Just KProp)
P.CEqual t1 t2 -> tcon (PC PEqual) [t1,t2] (Just KProp)
P.CGeq t1 t2 -> tcon (PC PGeq) [t1,t2] (Just KProp)
P.CArith t1 -> tcon (PC PArith) [t1] (Just KProp)
P.CCmp t1 -> tcon (PC PCmp) [t1] (Just KProp)
P.CLocated p r1 -> kInRange r1 (checkProp p)
P.CType _ -> panic "checkProp" [ "Unexpected CType", show prop ]
-- | Check that a type has the expected kind.
checkKind :: Type -- ^ Kind-checked type
-> Maybe Kind -- ^ Expected kind (if any)
-> Kind -- ^ Inferred kind
-> KindM Type -- ^ A type consistent with expectations.
checkKind _ (Just k1) k2
| k1 /= k2 = do kRecordError (KindMismatch k1 k2)
kNewType (text "kind error") k1
checkKind t _ _ = return t
cryptol-2.4.0/src/Cryptol/TypeCheck/Monad.hs 0000644 0000000 0000000 00000063771 12737220176 017120 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RecursiveDo #-}
module Cryptol.TypeCheck.Monad
( module Cryptol.TypeCheck.Monad
, module Cryptol.TypeCheck.InferTypes
) where
import Cryptol.ModuleSystem.Name (FreshM(..),Supply)
import Cryptol.Parser.Position
import qualified Cryptol.Parser.AST as P
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst
import Cryptol.TypeCheck.Unify(mgu, Result(..), UnificationError(..))
import Cryptol.TypeCheck.InferTypes
import qualified Cryptol.TypeCheck.Solver.CrySAT as CrySAT
import Cryptol.Utils.PP(pp, (<+>), Doc, text, quotes)
import Cryptol.Utils.Panic(panic)
import qualified Control.Applicative as A
import Control.Monad.Fix(MonadFix(..))
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Map (Map)
import Data.Set (Set)
import Data.List(find, minimumBy, groupBy, sortBy)
import Data.Maybe(mapMaybe)
import Data.Function(on)
import MonadLib hiding (mapM)
import GHC.Generics (Generic)
import Control.DeepSeq
import Prelude ()
import Prelude.Compat
-- | Information needed for type inference.
data InferInput = InferInput
{ inpRange :: Range -- ^ Location of program source
, inpVars :: Map Name Schema -- ^ Variables that are in scope
, inpTSyns :: Map Name TySyn -- ^ Type synonyms that are in scope
, inpNewtypes :: Map Name Newtype -- ^ Newtypes in scope
, inpNameSeeds :: NameSeeds -- ^ Private state of type-checker
, inpMonoBinds :: Bool -- ^ Should local bindings without
-- signatures be monomorphized?
, inpSolverConfig :: SolverConfig -- ^ Options for the constraint solver
, inpPrimNames :: !PrimMap -- ^ The mapping from 'Ident' to 'Name',
-- for names that the typechecker
-- needs to refer to.
, inpSupply :: !Supply -- ^ The supply for fresh name generation
} deriving Show
-- | This is used for generating various names.
data NameSeeds = NameSeeds
{ seedTVar :: !Int
, seedGoal :: !Int
} deriving (Show, Generic, NFData)
-- | The initial seeds, used when checking a fresh program.
nameSeeds :: NameSeeds
nameSeeds = NameSeeds { seedTVar = 10, seedGoal = 0 }
-- | The results of type inference.
data InferOutput a
= InferFailed [(Range,Warning)] [(Range,Error)]
-- ^ We found some errors
| InferOK [(Range,Warning)] NameSeeds Supply a
-- ^ Type inference was successful.
deriving Show
runInferM :: TVars a => InferInput -> InferM a -> IO (InferOutput a)
runInferM info (IM m) = CrySAT.withSolver (inpSolverConfig info) $ \solver ->
do rec ro <- return RO { iRange = inpRange info
, iVars = Map.map ExtVar (inpVars info)
, iTVars = []
, iTSyns = fmap mkExternal (inpTSyns info)
, iNewtypes = fmap mkExternal (inpNewtypes info)
, iSolvedHasLazy = iSolvedHas finalRW -- RECURSION
, iMonoBinds = inpMonoBinds info
, iSolver = solver
, iPrimNames = inpPrimNames info
}
(result, finalRW) <- runStateT rw
$ runReaderT ro m -- RECURSION
let theSu = iSubst finalRW
defSu = defaultingSubst theSu
warns = [(r,apSubst theSu w) | (r,w) <- iWarnings finalRW ]
case iErrors finalRW of
[] ->
case (iCts finalRW, iHasCts finalRW) of
(cts,[])
| nullGoals cts
-> return $ InferOK warns
(iNameSeeds finalRW)
(iSupply finalRW)
(apSubst defSu result)
(cts,has) -> return $ InferFailed warns
$ dropErrorsFromSameLoc
[ ( goalRange g
, UnsolvedGoal False (apSubst theSu g)
) | g <- fromGoals cts ++ map hasGoal has
]
errs -> return $ InferFailed warns
$ dropErrorsFromSameLoc
[(r,apSubst theSu e) | (r,e) <- errs]
where
mkExternal x = (IsExternal, x)
rw = RW { iErrors = []
, iWarnings = []
, iSubst = emptySubst
, iExistTVars = []
, iNameSeeds = inpNameSeeds info
, iCts = emptyGoals
, iHasCts = []
, iSolvedHas = Map.empty
, iSupply = inpSupply info
}
dropErrorsFromSameLoc = map chooseBestError . groupBy ((==) `on` fst)
. sortBy (cmpRange `on` fst)
addErrorSize (r,e) = (length (show (pp e)), (r,e))
chooseBestError = snd . minimumBy (compare `on` fst) . map addErrorSize
-- The actual order does not matter
cmpRange (Range x y z) (Range a b c) = compare (x,y,z) (a,b,c)
newtype InferM a = IM { unIM :: ReaderT RO (StateT RW IO) a }
data DefLoc = IsLocal | IsExternal
-- | Read-only component of the monad.
data RO = RO
{ iRange :: Range -- ^ Source code being analysed
, iVars :: Map Name VarType -- ^ Type of variable that are in scope
{- NOTE: We assume no shadowing between these two, so it does not matter
where we look first. Similarly, we assume no shadowing with
the existential type variable (in RW). See `checkTShadowing`. -}
, iTVars :: [TParam] -- ^ Type variable that are in scope
, iTSyns :: Map Name (DefLoc, TySyn) -- ^ Type synonyms that are in scope
, iNewtypes :: Map Name (DefLoc, Newtype)
-- ^ Newtype declarations in scope
--
-- NOTE: type synonyms take precedence over newtype. The reason is
-- that we can define local type synonyms, but not local newtypes.
-- So, either a type-synonym shadows a newtype, or it was declared
-- at the top-level, but then there can't be a newtype with the
-- same name (this should be caught by the renamer).
, iSolvedHasLazy :: Map Int (Expr -> Expr)
-- ^ NOTE: This field is lazy in an important way! It is the
-- final version of `iSolvedHas` in `RW`, and the two are tied
-- together through recursion. The field is here so that we can
-- look thing up before they are defined, which is OK because we
-- don't need to know the results until everything is done.
, iMonoBinds :: Bool
-- ^ When this flag is set to true, bindings that lack signatures
-- in where-blocks will never be generalized. Bindings with type
-- signatures, and all bindings at top level are unaffected.
, iSolver :: CrySAT.Solver
, iPrimNames :: !PrimMap
}
-- | Read-write component of the monad.
data RW = RW
{ iErrors :: ![(Range,Error)] -- ^ Collected errors
, iWarnings :: ![(Range,Warning)] -- ^ Collected warnings
, iSubst :: !Subst -- ^ Accumulated substitution
, iExistTVars :: [Map Name Type]
-- ^ These keeps track of what existential type variables are available.
-- When we start checking a function, we push a new scope for
-- its arguments, and we pop it when we are done checking the function
-- body. The front element of the list is the current scope, which is
-- the only thing that will be modified, as follows. When we encounter
-- a existential type variable:
-- 1. we look in all scopes to see if it is already defined.
-- 2. if it was not defined, we create a fresh type variable,
-- and we add it to the current scope.
-- 3. it is an error if we encounter an existential variable but we
-- have no current scope.
, iSolvedHas :: Map Int (Expr -> Expr)
-- ^ Selector constraints that have been solved (ref. iSolvedSelectorsLazy)
-- Generating names
, iNameSeeds :: !NameSeeds
-- Constraints that need solving
, iCts :: !Goals -- ^ Ordinary constraints
, iHasCts :: ![HasGoal]
{- ^ Tuple/record projection constraints. The `Int` is the "name"
of the constraint, used so that we can name it solution properly. -}
, iSupply :: !Supply
}
instance Functor InferM where
fmap f (IM m) = IM (fmap f m)
instance A.Applicative InferM where
pure = return
(<*>) = ap
instance Monad InferM where
return x = IM (return x)
fail x = IM (fail x)
IM m >>= f = IM (m >>= unIM . f)
instance MonadFix InferM where
mfix f = IM (mfix (unIM . f))
instance FreshM InferM where
liftSupply f = IM $
do rw <- get
let (a,s') = f (iSupply rw)
set rw { iSupply = s' }
return a
io :: IO a -> InferM a
io m = IM $ inBase m
-- | The monadic computation is about the given range of source code.
-- This is useful for error reporting.
inRange :: Range -> InferM a -> InferM a
inRange r (IM m) = IM $ mapReader (\ro -> ro { iRange = r }) m
inRangeMb :: Maybe Range -> InferM a -> InferM a
inRangeMb Nothing m = m
inRangeMb (Just r) m = inRange r m
-- | This is the current range that we are working on.
curRange :: InferM Range
curRange = IM $ asks iRange
-- | Report an error.
recordError :: Error -> InferM ()
recordError e =
do r <- curRange
IM $ sets_ $ \s -> s { iErrors = (r,e) : iErrors s }
recordWarning :: Warning -> InferM ()
recordWarning w =
do r <- curRange
IM $ sets_ $ \s -> s { iWarnings = (r,w) : iWarnings s }
getSolver :: InferM CrySAT.Solver
getSolver =
do RO { .. } <- IM ask
return iSolver
-- | Retrieve the mapping between identifiers and declarations in the prelude.
getPrimMap :: InferM PrimMap
getPrimMap =
do RO { .. } <- IM ask
return iPrimNames
--------------------------------------------------------------------------------
newGoal :: ConstraintSource -> Prop -> InferM Goal
newGoal goalSource goal =
do goalRange <- curRange
return Goal { .. }
-- | Record some constraints that need to be solved.
-- The string explains where the constraints came from.
newGoals :: ConstraintSource -> [Prop] -> InferM ()
newGoals src ps = addGoals =<< mapM (newGoal src) ps
{- | The constraints are removed, and returned to the caller.
The substitution IS applied to them. -}
getGoals :: InferM [Goal]
getGoals =
do goals <- applySubst =<< IM (sets $ \s -> (iCts s, s { iCts = emptyGoals }))
return (fromGoals goals)
-- | Add a bunch of goals that need solving.
addGoals :: [Goal] -> InferM ()
addGoals gs = IM $ sets_ $ \s -> s { iCts = foldl (flip insertGoal) (iCts s) gs }
-- | Collect the goals emitted by the given sub-computation.
-- Does not emit any new goals.
collectGoals :: InferM a -> InferM (a, [Goal])
collectGoals m =
do origGs <- applySubst =<< getGoals'
a <- m
newGs <- getGoals
setGoals' origGs
return (a, newGs)
where
-- retrieve the type map only
getGoals' = IM $ sets $ \ RW { .. } -> (iCts, RW { iCts = emptyGoals, .. })
-- set the type map directly
setGoals' gs = IM $ sets $ \ RW { .. } -> ((), RW { iCts = gs, .. })
{- | Record a constraint that when we select from the first type,
we should get a value of the second type.
The returned function should be used to wrap the expression from
which we are selecting (i.e., the record or tuple). Plese note
that the resulting expression should not be forced before the
constraint is solved.
-}
newHasGoal :: P.Selector -> Type -> Type -> InferM (Expr -> Expr)
newHasGoal l ty f =
do goalName <- newGoalName
g <- newGoal CtSelector (pHas l ty f)
IM $ sets_ $ \s -> s { iHasCts = HasGoal goalName g : iHasCts s }
solns <- IM $ fmap iSolvedHasLazy ask
return $ case Map.lookup goalName solns of
Just e1 -> e1
Nothing -> panic "newHasGoal" ["Unsolved has goal in result"]
-- | Add a previously generate has constrained
addHasGoal :: HasGoal -> InferM ()
addHasGoal g = IM $ sets_ $ \s -> s { iHasCts = g : iHasCts s }
-- | Get the `Has` constraints. Each of this should either be solved,
-- or added back using `addHasGoal`.
getHasGoals :: InferM [HasGoal]
getHasGoals = do gs <- IM $ sets $ \s -> (iHasCts s, s { iHasCts = [] })
applySubst gs
-- | Specify the solution (`Expr -> Expr`) for the given constraint (`Int`).
solveHasGoal :: Int -> (Expr -> Expr) -> InferM ()
solveHasGoal n e =
IM $ sets_ $ \s -> s { iSolvedHas = Map.insert n e (iSolvedHas s) }
--------------------------------------------------------------------------------
newName :: (NameSeeds -> (a , NameSeeds)) -> InferM a
newName upd = IM $ sets $ \s -> let (x,seeds) = upd (iNameSeeds s)
in (x, s { iNameSeeds = seeds })
-- | Generate a new name for a goal.
newGoalName :: InferM Int
newGoalName = newName $ \s -> let x = seedGoal s
in (x, s { seedGoal = x + 1})
-- | Generate a new free type variable.
newTVar :: Doc -> Kind -> InferM TVar
newTVar src k = newTVar' src Set.empty k
-- | Generate a new free type variable that depends on these additional
-- type parameters.
newTVar' :: Doc -> Set TVar -> Kind -> InferM TVar
newTVar' src extraBound k =
do bound <- getBoundInScope
let vs = Set.union extraBound bound
newName $ \s -> let x = seedTVar s
in (TVFree x k vs src, s { seedTVar = x + 1 })
-- | Generate a new free type variable.
newTParam :: Maybe Name -> Kind -> InferM TParam
newTParam nm k = newName $ \s -> let x = seedTVar s
in (TParam { tpUnique = x
, tpKind = k
, tpName = nm
}
, s { seedTVar = x + 1 })
-- | Generate an unknown type. The doc is a note about what is this type about.
newType :: Doc -> Kind -> InferM Type
newType src k = TVar `fmap` newTVar src k
--------------------------------------------------------------------------------
-- | Record that the two types should be syntactically equal.
unify :: Type -> Type -> InferM [Prop]
unify t1 t2 =
do t1' <- applySubst t1
t2' <- applySubst t2
case mgu t1' t2' of
OK (su1,ps) -> extendSubst su1 >> return ps
Error err ->
do case err of
UniTypeLenMismatch _ _ -> recordError (TypeMismatch t1' t2')
UniTypeMismatch s1 s2 -> recordError (TypeMismatch s1 s2)
UniKindMismatch k1 k2 -> recordError (KindMismatch k1 k2)
UniRecursive x t -> recordError (RecursiveType (TVar x) t)
UniNonPolyDepends x vs -> recordError
(TypeVariableEscaped (TVar x) vs)
UniNonPoly x t -> recordError (NotForAll x t)
return []
-- | Apply the accumulated substitution to something with free type variables.
applySubst :: TVars t => t -> InferM t
applySubst t =
do su <- getSubst
return (apSubst su t)
-- | Get the substitution that we have accumulated so far.
getSubst :: InferM Subst
getSubst = IM $ fmap iSubst get
-- | Add to the accumulated substitution.
extendSubst :: Subst -> InferM ()
extendSubst su = IM $ sets_ $ \s -> s { iSubst = su @@ iSubst s }
-- | Variables that are either mentioned in the environment or in
-- a selector constraint.
varsWithAsmps :: InferM (Set TVar)
varsWithAsmps =
do env <- IM $ fmap (Map.elems . iVars) ask
fromEnv <- forM env $ \v ->
case v of
ExtVar sch -> getVars sch
CurSCC _ t -> getVars t
sels <- IM $ fmap (map (goal . hasGoal) . iHasCts) get
fromSels <- mapM getVars sels
fromEx <- (getVars . concatMap Map.elems) =<< IM (fmap iExistTVars get)
return (Set.unions fromEnv `Set.union` Set.unions fromSels
`Set.union` fromEx)
where
getVars x = fvs `fmap` applySubst x
--------------------------------------------------------------------------------
-- | Lookup the type of a variable.
lookupVar :: Name -> InferM VarType
lookupVar x =
do mb <- IM $ asks $ Map.lookup x . iVars
case mb of
Just t -> return t
Nothing ->
do mbNT <- lookupNewtype x
case mbNT of
Just nt -> return (ExtVar (newtypeConType nt))
Nothing -> do recordError $ UndefinedVariable x
a <- newType (text "type of" <+> pp x) KType
return $ ExtVar $ Forall [] [] a
-- | Lookup a type variable. Return `Nothing` if there is no such variable
-- in scope, in which case we must be dealing with a type constant.
lookupTVar :: Name -> InferM (Maybe Type)
lookupTVar x = IM $ asks $ fmap (TVar . tpVar) . find this . iTVars
where this tp = tpName tp == Just x
-- | Lookup the definition of a type synonym.
lookupTSyn :: Name -> InferM (Maybe TySyn)
lookupTSyn x = fmap (fmap snd . Map.lookup x) getTSyns
-- | Lookup the definition of a newtype
lookupNewtype :: Name -> InferM (Maybe Newtype)
lookupNewtype x = fmap (fmap snd . Map.lookup x) getNewtypes
-- | Check if we already have a name for this existential type variable and,
-- if so, return the definition. If not, try to create a new definition,
-- if this is allowed. If not, returns nothing.
existVar :: Name -> Kind -> InferM Type
existVar x k =
do scopes <- iExistTVars <$> IM get
case msum (map (Map.lookup x) scopes) of
Just ty -> return ty
Nothing ->
case scopes of
[] ->
do recordError $ ErrorMsg $
text "Undefined type" <+> quotes (pp x)
newType (text "undefined existential type varible" <+>
quotes (pp x)) k
sc : more ->
do ty <- newType (text "existential type variable"
<+> quotes (pp x)) k
IM $ sets_ $ \s -> s{ iExistTVars = Map.insert x ty sc : more }
return ty
-- | Returns the type synonyms that are currently in scope.
getTSyns :: InferM (Map Name (DefLoc,TySyn))
getTSyns = IM $ asks iTSyns
-- | Returns the newtype declarations that are in scope.
getNewtypes :: InferM (Map Name (DefLoc,Newtype))
getNewtypes = IM $ asks iNewtypes
-- | Get the set of bound type variables that are in scope.
getTVars :: InferM (Set Name)
getTVars = IM $ asks $ Set.fromList . mapMaybe tpName . iTVars
-- | Return the keys of the bound variables that are in scope.
getBoundInScope :: InferM (Set TVar)
getBoundInScope = IM $ asks $ Set.fromList . map tpVar . iTVars
-- | Retrieve the value of the `mono-binds` option.
getMonoBinds :: InferM Bool
getMonoBinds = IM (asks iMonoBinds)
{- | We disallow shadowing between type synonyms and type variables
because it is confusing. As a bonus, in the implementation we don't
need to worry about where we lookup things (i.e., in the variable or
type synonym environment. -}
checkTShadowing :: String -> Name -> InferM ()
checkTShadowing this new =
do ro <- IM ask
rw <- IM get
let shadowed =
do _ <- Map.lookup new (iTSyns ro)
return "type synonym"
`mplus`
do guard (new `elem` mapMaybe tpName (iTVars ro))
return "type variable"
`mplus`
do _ <- msum (map (Map.lookup new) (iExistTVars rw))
return "type"
case shadowed of
Nothing -> return ()
Just that ->
recordError $ ErrorMsg $
text "Type" <+> text this <+> quotes (pp new) <+>
text "shadows an existing" <+>
text that <+> text "with the same name."
-- | The sub-computation is performed with the given type parameter in scope.
withTParam :: TParam -> InferM a -> InferM a
withTParam p (IM m) =
do case tpName p of
Just x -> checkTShadowing "variable" x
Nothing -> return ()
IM $ mapReader (\r -> r { iTVars = p : iTVars r }) m
withTParams :: [TParam] -> InferM a -> InferM a
withTParams ps m = foldr withTParam m ps
-- | The sub-computation is performed with the given type-synonym in scope.
withTySyn :: TySyn -> InferM a -> InferM a
withTySyn t (IM m) =
do let x = tsName t
checkTShadowing "synonym" x
IM $ mapReader (\r -> r { iTSyns = Map.insert x (IsLocal,t) (iTSyns r) }) m
withNewtype :: Newtype -> InferM a -> InferM a
withNewtype t (IM m) =
IM $ mapReader
(\r -> r { iNewtypes = Map.insert (ntName t) (IsLocal,t)
(iNewtypes r) }) m
-- | The sub-computation is performed with the given variable in scope.
withVarType :: Name -> VarType -> InferM a -> InferM a
withVarType x s (IM m) =
IM $ mapReader (\r -> r { iVars = Map.insert x s (iVars r) }) m
withVarTypes :: [(Name,VarType)] -> InferM a -> InferM a
withVarTypes xs m = foldr (uncurry withVarType) m xs
withVar :: Name -> Schema -> InferM a -> InferM a
withVar x s = withVarType x (ExtVar s)
-- | The sub-computation is performed with the given variables in scope.
withMonoType :: (Name,Located Type) -> InferM a -> InferM a
withMonoType (x,lt) = withVar x (Forall [] [] (thing lt))
-- | The sub-computation is performed with the given variables in scope.
withMonoTypes :: Map Name (Located Type) -> InferM a -> InferM a
withMonoTypes xs m = foldr withMonoType m (Map.toList xs)
-- | The sub-computation is performed with the given type synonyms
-- and variables in scope.
withDecls :: ([TySyn], Map Name Schema) -> InferM a -> InferM a
withDecls (ts,vs) m = foldr withTySyn (foldr add m (Map.toList vs)) ts
where
add (x,t) = withVar x t
-- | Perform the given computation in a new scope (i.e., the subcomputation
-- may use existential type variables).
inNewScope :: InferM a -> InferM a
inNewScope m =
do curScopes <- iExistTVars <$> IM get
IM $ sets_ $ \s -> s { iExistTVars = Map.empty : curScopes }
a <- m
IM $ sets_ $ \s -> s { iExistTVars = curScopes }
return a
--------------------------------------------------------------------------------
-- Kind checking
newtype KindM a = KM { unKM :: ReaderT KRO (StateT KRW InferM) a }
data KRO = KRO { lazyTVars :: Map Name Type -- ^ lazy map, with tyvars.
, allowWild :: Bool -- ^ are type-wild cards allowed?
}
data KRW = KRW { typeParams :: Map Name Kind -- ^ kinds of (known) vars.
}
instance Functor KindM where
fmap f (KM m) = KM (fmap f m)
instance A.Applicative KindM where
pure = return
(<*>) = ap
instance Monad KindM where
return x = KM (return x)
fail x = KM (fail x)
KM m >>= k = KM (m >>= unKM . k)
{- | The arguments to this function are as follows:
(type param. name, kind signature (opt.), a type representing the param)
The type representing the parameter is just a thunk that we should not force.
The reason is that the type depnds on the kind of parameter, that we are
in the process of computing.
As a result we return the value of the sub-computation and the computed
kinds of the type parameters. -}
runKindM :: Bool -- Are type-wild cards allowed?
-> [(Name, Maybe Kind, Type)] -- ^ See comment
-> KindM a -> InferM (a, Map Name Kind)
runKindM wildOK vs (KM m) =
do (a,kw) <- runStateT krw (runReaderT kro m)
return (a, typeParams kw)
where
tys = Map.fromList [ (x,t) | (x,_,t) <- vs ]
kro = KRO { allowWild = wildOK, lazyTVars = tys }
krw = KRW { typeParams = Map.fromList [ (x,k) | (x,Just k,_) <- vs ] }
-- | This is what's returned when we lookup variables during kind checking.
data LkpTyVar = TLocalVar Type (Maybe Kind) -- ^ Locally bound variable.
| TOuterVar Type -- ^ An outer binding.
-- | Check if a name refers to a type variable.
kLookupTyVar :: Name -> KindM (Maybe LkpTyVar)
kLookupTyVar x = KM $
do vs <- lazyTVars `fmap` ask
ss <- get
case Map.lookup x vs of
Just t -> return $ Just $ TLocalVar t $ Map.lookup x $ typeParams ss
Nothing -> lift $ lift $ do t <- lookupTVar x
return (fmap TOuterVar t)
-- | Are type wild-cards OK in this context?
kWildOK :: KindM Bool
kWildOK = KM $ fmap allowWild ask
-- | Reports an error.
kRecordError :: Error -> KindM ()
kRecordError e = kInInferM $ recordError e
kRecordWarning :: Warning -> KindM ()
kRecordWarning w = kInInferM $ recordWarning w
-- | Generate a fresh unification variable of the given kind.
kNewType :: Doc -> Kind -> KindM Type
kNewType src k =
do tps <- KM $ do vs <- asks lazyTVars
return $ Set.fromList [ tv | TVar tv <- Map.elems vs ]
kInInferM $ TVar `fmap` newTVar' src tps k
-- | Lookup the definition of a type synonym.
kLookupTSyn :: Name -> KindM (Maybe TySyn)
kLookupTSyn x = kInInferM $ lookupTSyn x
-- | Lookup the definition of a newtype.
kLookupNewtype :: Name -> KindM (Maybe Newtype)
kLookupNewtype x = kInInferM $ lookupNewtype x
kExistTVar :: Name -> Kind -> KindM Type
kExistTVar x k = kInInferM $ existVar x k
-- | Replace the given bound variables with concrete types.
kInstantiateT :: Type -> [(TParam,Type)] -> KindM Type
kInstantiateT t as = return (apSubst su t)
where su = listSubst [ (tpVar x, t1) | (x,t1) <- as ]
{- | Record the kind for a local type variable.
This assumes that we already checked that there was no other valid
kind for the variable (if there was one, it gets over-written). -}
kSetKind :: Name -> Kind -> KindM ()
kSetKind v k = KM $ sets_ $ \s -> s{ typeParams = Map.insert v k (typeParams s)}
-- | The sub-computation is about the given range of the source code.
kInRange :: Range -> KindM a -> KindM a
kInRange r (KM m) = KM $
do e <- ask
s <- get
(a,s1) <- lift $ lift $ inRange r $ runStateT s $ runReaderT e m
set s1
return a
kNewGoals :: ConstraintSource -> [Prop] -> KindM ()
kNewGoals c ps = kInInferM $ newGoals c ps
kInInferM :: InferM a -> KindM a
kInInferM m = KM $ lift $ lift m
cryptol-2.4.0/src/Cryptol/TypeCheck/PP.hs 0000644 0000000 0000000 00000003364 12737220176 016371 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE FlexibleInstances, FlexibleContexts #-}
module Cryptol.TypeCheck.PP
( NameMap, WithNames(..)
, emptyNameMap
, ppWithNamesPrec, ppWithNames
, intToName, nameList
, dump
, module Cryptol.Utils.PP
) where
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List(transpose)
import Cryptol.Utils.PP
type NameMap = IntMap String
emptyNameMap :: NameMap
emptyNameMap = IntMap.empty
-- | This packages together a type with some names to be used to display
-- the variables. It is used for pretty printing types.
data WithNames a = WithNames a NameMap
ppWithNamesPrec :: PP (WithNames a) => NameMap -> Int -> a -> Doc
ppWithNamesPrec names prec t = ppPrec prec (WithNames t names)
ppWithNames :: PP (WithNames a) => NameMap -> a -> Doc
ppWithNames names t = ppWithNamesPrec names 0 t
dump :: PP (WithNames a) => a -> String
dump x = show (ppWithNames IntMap.empty x)
-- | Compute the n-th variant of a name (e.g., @a5@).
nameVariant :: Int -> String -> String
nameVariant 0 x = x
nameVariant n x = x ++ show n
-- | Compute all variants of a name: @a, a1, a2, a3, ...@
nameVariants :: String -> [String]
nameVariants x = map (`nameVariant` x) [ 0 .. ]
-- | Expand a list of base names into an infinite list of variations.
nameList :: [String] -> [String]
nameList names = concat $ transpose $ map nameVariants baseNames
where
baseNames | null names = map (:[]) [ 'a' .. 'z' ]
| otherwise = names
intToName :: Int -> String
intToName x = nameList [] !! x
cryptol-2.4.0/src/Cryptol/TypeCheck/Sanity.hs 0000644 0000000 0000000 00000035032 12737220176 017316 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.TypeCheck.Sanity
( tcExpr
, tcDecls
, tcModule
, ProofObligation
, Error(..)
, same
) where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst(apSubst, fvs, singleSubst)
import Cryptol.Utils.Ident
import qualified Data.Set as Set
import Data.List(sort, sortBy)
import Data.Function (on)
import MonadLib
import qualified Control.Applicative as A
import Data.Map ( Map )
import qualified Data.Map as Map
tcExpr :: Map Name Schema -> Expr -> Either Error (Schema, [ ProofObligation ])
tcExpr env e = runTcM env (exprSchema e)
tcDecls :: Map Name Schema -> [DeclGroup] -> Either Error [ ProofObligation ]
tcDecls env ds0 = case runTcM env (go ds0) of
Left err -> Left err
Right (_,ps) -> Right ps
where
go [] = return ()
go (d : ds) = do xs <- checkDeclGroup d
withVars xs (go ds)
tcModule :: Map Name Schema -> Module -> Either Error [ ProofObligation ]
tcModule env m = tcDecls env (mDecls m)
--------------------------------------------------------------------------------
tMono :: Type -> Schema
tMono = Forall [] []
isMono :: Schema -> Maybe Type
isMono s =
case s of
Forall [] [] t -> Just t
_ -> Nothing
--------------------------------------------------------------------------------
-- | Validate a type, returning its kind.
checkType :: Type -> TcM Kind
checkType ty =
case ty of
TUser _ _ t -> checkType t -- Maybe check synonym too?
TCon tc ts ->
do ks <- mapM checkType ts
checkKind (kindOf tc) ks
TVar tv -> lookupTVar tv
TRec fs ->
do forM_ fs $ \(_,t) ->
do k <- checkType t
unless (k == KType) $ reportError $ KindMismatch KType k
return KType
where
checkKind k [] = case k of
_ :-> _ -> reportError $ NotEnoughArgumentsInKind k
KProp -> return k
KNum -> return k
KType -> return k
checkKind (k1 :-> k2) (k : ks)
| k == k1 = checkKind k2 ks
| otherwise = reportError $ KindMismatch k1 k
checkKind k ks = reportError $ BadTypeApplication k ks
-- | Check that the type is valid, and it has the given kind.
checkTypeIs :: Kind -> Type -> TcM ()
checkTypeIs k ty =
do k1 <- checkType ty
unless (k == k1) $ reportError $ KindMismatch k k1
-- | Check that this is a valid schema.
checkSchema :: Schema -> TcM ()
checkSchema (Forall as ps t) = foldr withTVar check as
where check = do mapM_ (checkTypeIs KProp) ps
checkTypeIs KType t
class Same a where
same :: a -> a -> Bool
instance Same a => Same [a] where
same [] [] = True
same (x : xs) (y : ys) = same x y && same xs ys
same _ _ = False
instance Same Type where
same t1 t2 = tNoUser t1 == tNoUser t2
instance Same Schema where
same (Forall xs ps s) (Forall ys qs t) = same xs ys && same ps qs && same s t
instance Same TParam where
same x y = tpName x == tpName y && tpKind x == tpKind y
--------------------------------------------------------------------------------
-- | Check that the expression is well-formed, and compute its type.
-- Reports an error if the expression is not of a mono type.
exprType :: Expr -> TcM Type
exprType expr =
do s <- exprSchema expr
case isMono s of
Just t -> return t
Nothing -> reportError (ExpectedMono s)
-- | Check that the expression is well-formed, and compute its schema.
exprSchema :: Expr -> TcM Schema
exprSchema expr =
case expr of
EList es t ->
do checkTypeIs KType t
forM_ es $ \e ->
do t1 <- exprType e
unless (same t1 t) $
reportError $ TypeMismatch (tMono t) (tMono t1)
return $ tMono $ tSeq (tNum (length es)) t
ETuple es ->
fmap (tMono . tTuple) (mapM exprType es)
ERec fs ->
do fs1 <- forM fs $ \(f,e) -> do t <- exprType e
return (f,t)
return $ tMono $ TRec fs1
ESel e sel ->
do t <- exprType e
case sel of
TupleSel n mb ->
case tNoUser t of
TCon (TC (TCTuple sz)) ts ->
do case mb of
Just sz1 -> when (sz /= sz1) $
reportError (UnexpectedTupleShape sz1 sz)
Nothing -> return ()
unless (n < sz) $
reportError (TupleSelectorOutOfRange n sz)
return $ tMono $ ts !! n
_ -> reportError $ BadSelector sel t
RecordSel f mb ->
case tNoUser t of
TRec fs ->
do case mb of
Nothing -> return ()
Just fs1 ->
do let ns = sort (map fst fs)
ns1 = sort fs1
unless (ns == ns1) $
reportError $ UnexpectedRecordShape ns1 ns
case lookup f fs of
Nothing -> reportError $ MissingField f $ map fst fs
Just ft -> return $ tMono ft
_ -> reportError $ BadSelector sel t
ListSel _ mb ->
case tNoUser t of
TCon (TC TCSeq) [ n, elT ] ->
do case mb of
Nothing -> return ()
Just len ->
case tNoUser n of
TCon (TC (TCNum m)) []
| m == fromIntegral len -> return ()
_ -> reportError $ UnexpectedSequenceShape len n
return $ tMono elT
_ -> reportError $ BadSelector sel t
EIf e1 e2 e3 ->
do ty <- exprType e1
unless (same tBit ty) $
reportError $ TypeMismatch (tMono tBit) (tMono ty)
t1 <- exprType e2
t2 <- exprType e3
unless (same t1 t2) $
reportError $ TypeMismatch (tMono t1) (tMono t2)
return $ tMono t1
EComp t e mss ->
do checkTypeIs KType t
(xs,ls) <- unzip `fmap` mapM checkArm mss
-- XXX: check no duplicates
elT <- withVars (concat xs) $ exprType e
case ls of
[] -> return ()
_ -> convertible t (tSeq (foldr1 tMin ls) elT)
return (tMono t)
EVar x -> lookupVar x
ETAbs a e ->
do Forall as p t <- withTVar a (exprSchema e)
when (any (== a) as) $
reportError $ RepeatedVariableInForall a
return (Forall (a : as) p t)
ETApp e t ->
do k <- checkType t
s <- exprSchema e
case s of
Forall (a : as) ps t1 ->
do let vs = fvs t
forM_ (map tpVar as) $ \b ->
when (b `Set.member` vs) $ reportError $ Captured b
let k' = kindOf a
unless (k == k') $ reportError $ KindMismatch k' k
let su = singleSubst (tpVar a) t
return $ Forall as (apSubst su ps) (apSubst su t1)
Forall [] _ _ -> reportError BadInstantiation
EApp e1 e2 ->
do t1 <- exprType e1
t2 <- exprType e2
case tNoUser t1 of
TCon (TC TCFun) [ a, b ]
| same a t2 -> return (tMono b)
tf -> reportError (BadApplication tf t1)
EAbs x t e ->
do checkTypeIs KType t
res <- withVar x t (exprType e)
return $ tMono $ tFun t res
EProofAbs p e ->
do checkTypeIs KProp p
withAsmp p $ do Forall as ps t <- exprSchema e
return $ Forall as (p : ps) t
EProofApp e ->
do Forall as ps t <- exprSchema e
case (as,ps) of
([], p:qs) -> do proofObligation p
return (Forall [] qs t)
([], _) -> reportError BadProofNoAbs
(_,_) -> reportError (BadProofTyVars as)
ECast e t ->
do checkTypeIs KType t
t1 <- exprType e
convertible t t1
return (tMono t)
-- XXX: Check that defined things are disitnct?
EWhere e dgs ->
let go [] = exprSchema e
go (d : ds) = do xs <- checkDeclGroup d
withVars xs (go ds)
in go dgs
-- | Check if the one type is convertible to the other.
convertible :: Type -> Type -> TcM ()
convertible t1 t2
| k1 /= k2 = reportError (KindMismatch k1 k2)
| k1 == KNum = proofObligation (t1 =#= t2)
where
k1 = kindOf t1
k2 = kindOf t2
convertible t1 t2 = go t1 t2
where
go ty1 ty2 =
let err = reportError $ TypeMismatch (tMono ty1) (tMono ty2)
other = tNoUser ty2
goMany [] [] = return ()
goMany (x : xs) (y : ys) = convertible x y >> goMany xs ys
goMany _ _ = err
in case ty1 of
TUser _ _ s -> go s ty2
TVar x -> case other of
TVar y | x == y -> return ()
_ -> err
TCon tc1 ts1 -> case other of
TCon tc2 ts2
| tc1 == tc2 -> goMany ts1 ts2
_ -> err
TRec fs ->
case other of
TRec gs ->
do let order = sortBy (compare `on` fst)
fs1 = order fs
gs1 = order gs
unless (map fst fs1 == map fst gs1) err
goMany (map snd fs1) (map snd gs1)
_ -> err
--------------------------------------------------------------------------------
-- | Check a declaration. The boolean indicates if we should check the siganture
checkDecl :: Bool -> Decl -> TcM (Name, Schema)
checkDecl checkSig d =
case dDefinition d of
DPrim ->
do when checkSig $ checkSchema $ dSignature d
return (dName d, dSignature d)
DExpr e ->
do let s = dSignature d
when checkSig $ checkSchema s
s1 <- exprSchema e
unless (same s s1) $
reportError $ TypeMismatch s s1
return (dName d, s)
checkDeclGroup :: DeclGroup -> TcM [(Name, Schema)]
checkDeclGroup dg =
case dg of
NonRecursive d -> do x <- checkDecl True d
return [x]
Recursive ds ->
do xs <- forM ds $ \d ->
do checkSchema (dSignature d)
return (dName d, dSignature d)
withVars xs $ mapM (checkDecl False) ds
checkMatch :: Match -> TcM ((Name, Schema), Type)
checkMatch ma =
case ma of
From x t e ->
do checkTypeIs KType t
t1 <- exprType e
case tNoUser t1 of
TCon (TC TCSeq) [ l, el ]
| same t el -> return ((x, tMono t), l)
| otherwise -> reportError $ TypeMismatch (tMono t) (tMono el)
_ -> reportError $ BadMatch t1
Let d -> do x <- checkDecl True d
return (x, tNum (1 :: Int))
checkArm :: [Match] -> TcM ([(Name, Schema)], Type)
checkArm [] = reportError EmptyArm
checkArm [m] = do (x,l) <- checkMatch m
return ([x], l)
checkArm (m : ms) =
do (x, l) <- checkMatch m
(xs, l1) <- withVars [x] $ checkArm ms
let newLen = l .*. l1
return $ if fst x `elem` map fst xs
then (xs, newLen)
else (x : xs, newLen)
--------------------------------------------------------------------------------
data RO = RO
{ roTVars :: Map Int TParam
, roAsmps :: [Prop]
, roVars :: Map Name Schema
}
type ProofObligation = Schema -- but the type is of kind Prop
data RW = RW
{ woProofObligations :: [ProofObligation]
}
newtype TcM a = TcM (ReaderT RO (ExceptionT Error (StateT RW Id)) a)
instance Functor TcM where
fmap = liftM
instance A.Applicative TcM where
pure = return
(<*>) = ap
instance Monad TcM where
return a = TcM (return a)
fail x = TcM (fail x)
TcM m >>= f = TcM (do a <- m
let TcM m1 = f a
m1)
runTcM :: Map Name Schema -> TcM a -> Either Error (a, [ProofObligation])
runTcM env (TcM m) =
case runM m ro rw of
(Left err, _) -> Left err
(Right a, s) -> Right (a, woProofObligations s)
where
ro = RO { roTVars = Map.empty
, roAsmps = []
, roVars = env
}
rw = RW { woProofObligations = [] }
data Error =
TypeMismatch Schema Schema -- ^ expected, actual
| ExpectedMono Schema -- ^ expected a mono type, got this
| TupleSelectorOutOfRange Int Int
| MissingField Ident [Ident]
| UnexpectedTupleShape Int Int
| UnexpectedRecordShape [Ident] [Ident]
| UnexpectedSequenceShape Int Type
| BadSelector Selector Type
| BadInstantiation
| Captured TVar
| BadProofNoAbs
| BadProofTyVars [TParam]
| KindMismatch Kind Kind
| NotEnoughArgumentsInKind Kind
| BadApplication Type Type
| FreeTypeVariable TVar
| BadTypeApplication Kind [Kind]
| RepeatedVariableInForall TParam
| BadMatch Type
| EmptyArm
| UndefinedTypeVaraible TVar
| UndefinedVariable Name
deriving Show
reportError :: Error -> TcM a
reportError e = TcM (raise e)
withTVar :: TParam -> TcM a -> TcM a
withTVar a (TcM m) = TcM $
do ro <- ask
local ro { roTVars = Map.insert (tpUnique a) a (roTVars ro) } m
withAsmp :: Prop -> TcM a -> TcM a
withAsmp p (TcM m) = TcM $
do ro <- ask
local ro { roAsmps = p : roAsmps ro } m
withVar :: Name -> Type -> TcM a -> TcM a
withVar x t = withVars [(x,tMono t)]
withVars :: [(Name, Schema)] -> TcM a -> TcM a
withVars xs (TcM m) = TcM $
do ro <- ask
local ro { roVars = Map.union (Map.fromList xs) (roVars ro) } m
proofObligation :: Prop -> TcM ()
proofObligation p = TcM $
do ro <- ask
sets_ $ \rw -> rw { woProofObligations =
Forall (Map.elems (roTVars ro)) (roAsmps ro) p
: woProofObligations rw }
lookupTVar :: TVar -> TcM Kind
lookupTVar x =
case x of
TVFree {} -> reportError (FreeTypeVariable x)
TVBound u k ->
do ro <- TcM ask
case Map.lookup u (roTVars ro) of
Just tp
| kindOf tp == k -> return k
| otherwise -> reportError $ KindMismatch (kindOf tp) k
Nothing -> reportError $ UndefinedTypeVaraible x
lookupVar :: Name -> TcM Schema
lookupVar x =
do ro <- TcM ask
case Map.lookup x (roVars ro) of
Just s -> return s
Nothing -> reportError $ UndefinedVariable x
cryptol-2.4.0/src/Cryptol/TypeCheck/Solve.hs 0000644 0000000 0000000 00000055603 12737220176 017145 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE PatternGuards, BangPatterns, RecordWildCards #-}
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Solve
( simplifyAllConstraints
, proveImplication
, wfType
, wfTypeFunction
, improveByDefaultingWith
, defaultReplExpr
, simpType
, simpTypeMaybe
) where
import Cryptol.Parser.Position (emptyRange)
import Cryptol.TypeCheck.PP(pp)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Monad
import Cryptol.TypeCheck.Subst
(apSubst,fvs,singleSubst,substToList, isEmptySubst,
emptySubst,Subst,listSubst, (@@), Subst,
apSubstMaybe)
import Cryptol.TypeCheck.Solver.Class
import Cryptol.TypeCheck.Solver.Selector(tryHasGoal)
import qualified Cryptol.TypeCheck.Solver.Numeric.AST as Num
import qualified Cryptol.TypeCheck.Solver.Numeric.ImportExport as Num
import Cryptol.TypeCheck.Solver.Numeric.Interval (Interval)
import qualified Cryptol.TypeCheck.Solver.Numeric.Simplify1 as Num
import qualified Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr as Num
import qualified Cryptol.TypeCheck.Solver.CrySAT as Num
import Cryptol.TypeCheck.Solver.CrySAT (debugBlock, DebugLog(..))
import Cryptol.TypeCheck.Solver.Simplify (tryRewritePropAsSubst)
import Cryptol.Utils.PP (text)
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.Misc(anyJust)
import Control.Monad (unless, guard)
import Data.Either(partitionEithers)
import Data.Maybe(catMaybes, fromMaybe, mapMaybe)
import Data.Map ( Map )
import qualified Data.Map as Map
import Data.Set ( Set )
import qualified Data.Set as Set
{- | Add additional constraints that ensure validity of type function.
Note that these constraints do not introduce additional malformed types,
so the well-formedness constraints are guaranteed to be well-formed.
This assumes that the parameters are well-formed. -}
wfTypeFunction :: TFun -> [Type] -> [Prop]
wfTypeFunction TCSub [a,b] = [ a >== b, pFin b]
wfTypeFunction TCDiv [a,b] = [ b >== tOne, pFin a ]
wfTypeFunction TCMod [a,b] = [ b >== tOne, pFin a ]
wfTypeFunction TCLenFromThen [a,b,w] =
[ pFin a, pFin b, pFin w, a =/= b, w >== tWidth a ]
wfTypeFunction TCLenFromThenTo [a,b,c] = [ pFin a, pFin b, pFin c, a =/= b ]
wfTypeFunction _ _ = []
-- | Add additional constraints that ensure the validity of a type.
wfType :: Type -> [Prop]
wfType t =
case t of
TCon c ts ->
let ps = concatMap wfType ts
in case c of
TF f -> wfTypeFunction f ts ++ ps
_ -> ps
TVar _ -> []
TUser _ _ s -> wfType s
TRec fs -> concatMap (wfType . snd) fs
--------------------------------------------------------------------------------
simplifyAllConstraints :: InferM ()
simplifyAllConstraints =
do mapM_ tryHasGoal =<< getHasGoals
gs <- getGoals
solver <- getSolver
(mb,su) <- io (simpGoals' solver gs)
extendSubst su
case mb of
Right gs1 -> addGoals gs1
Left badGs -> mapM_ (recordError . UnsolvedGoal True) badGs
proveImplication :: Name -> [TParam] -> [Prop] -> [Goal] -> InferM Subst
proveImplication lnam as ps gs =
do evars <- varsWithAsmps
solver <- getSolver
(mbErr,su) <- io (proveImplicationIO solver lnam evars as ps gs)
case mbErr of
Right ws -> mapM_ recordWarning ws
Left err -> recordError err
return su
proveImplicationIO :: Num.Solver
-> Name -- ^ Checking this function
-> Set TVar -- ^ These appear in the env., and we should
-- not try to default the
-> [TParam] -- ^ Type parameters
-> [Prop] -- ^ Assumed constraint
-> [Goal] -- ^ Collected constraints
-> IO (Either Error [Warning], Subst)
proveImplicationIO _ _ _ _ [] [] = return (Right [], emptySubst)
proveImplicationIO s lname varsInEnv as ps gs =
debugBlock s "proveImplicationIO" $
do debugBlock s "assumes" (debugLog s ps)
debugBlock s "shows" (debugLog s gs)
debugLog s "1. ------------------"
_simpPs <- Num.assumeProps s ps
mbImps <- Num.check s
debugLog s "2. ------------------"
case mbImps of
Nothing ->
do debugLog s "(contradiction in assumptions)"
return (Left $ UnusableFunction lname ps, emptySubst)
Just (imps,extra) ->
do let su = importImps imps
gs0 = apSubst su gs
debugBlock s "improvement from assumptions:" $ debugLog s su
let (scs,invalid) = importSideConds extra
unless (null invalid) $
panic "proveImplicationIO" ( "Unable to import all side conditions:"
: map (show . Num.ppProp) invalid )
let gs1 = filter ((`notElem` ps) . goal) gs0
debugLog s "3. ---------------------"
(mb,su1) <- simpGoals' s (scs ++ gs1)
case mb of
Left badGs -> reportUnsolved badGs (su1 @@ su)
Right [] -> return (Right [], su1 @@ su)
Right us ->
-- Last hope: try to default stuff
do let vs = Set.filter isFreeTV $ fvs $ map goal us
dVars = Set.toList (vs `Set.difference` varsInEnv)
(_,us1,su2,ws) <- improveByDefaultingWith s dVars us
case us1 of
[] -> return (Right ws, su2 @@ su1 @@ su)
_ -> reportUnsolved us1 (su2 @@ su1 @@ su)
where
reportUnsolved us su =
return ( Left $ UnsolvedDelayedCt
$ DelayedCt { dctSource = lname
, dctForall = as
, dctAsmps = ps
, dctGoals = us
}, su)
{- Constraints and satisfiability:
1. [Satisfiable] A collection of constraints is _satisfiable_, if there is an
assignment for the variables that make all constraints true.
2. [Valid] If a constraint is satisfiable for any assignment of its free
variables, then it is _valid_, and may be ommited.
3. [Partial] A constraint may _partial_, which means that under some
assignment it is neither true nor false. For example:
`x - y > 5` is true for `{ x = 15, y = 3 }`, it is false for
`{ x = 5, y = 4 }`, and it is neither for `{ x = 1, y = 2 }`.
Note that constraints that are always true or undefined are NOT
valid, as there are assignemntes for which they are not true.
An example of such constraint is `x - y >= 0`.
4. [Provability] Instead of thinking of three possible values for
satisfiability (i.e., true, false, and unknown), we could instead
think of asking: "Is constraint C provable". This essentailly
maps "true" to "true", and "false,unknown" to "false", if we
treat constraints with malformed parameters as unprovable.
-}
{-
The plan:
1. Start with a set of constraints, CS
2. Compute its well-defined closure, DS.
3. Simplify constraints: evaluate terms in constraints as much as possible
4. Solve: eliminate constraints that are true
5. Check for consistency
6. Compute improvements
7. For each type in the improvements, add well-defined constraints
8. Instantiate constraints with substitution
9. Goto 3
-}
simpGoals' :: Num.Solver -> [Goal] -> IO (Either [Goal] [Goal], Subst)
simpGoals' s gs0 = go emptySubst [] (wellFormed gs0 ++ gs0)
where
-- Assumes that the well-formed constraints are themselves well-formed.
wellFormed gs = [ g { goal = p } | g <- gs, p <- wfType (goal g) ]
go su old [] = return (Right old, su)
go su old gs =
do gs1 <- simplifyConstraintTerms s gs
res <- solveConstraints s old gs1
case res of
Left err -> return (Left err, su)
Right gs2 ->
do let gs3 = gs2 ++ old
mb <- computeImprovements s gs3
case mb of
Left err -> return (Left err, su)
Right impSu ->
let (unchanged,changed) =
partitionEithers (map (applyImp impSu) gs3)
new = wellFormed changed
in go (impSu @@ su) unchanged (new ++ changed)
applyImp su g = case apSubstMaybe su (goal g) of
Nothing -> Left g
Just p -> Right g { goal = p }
{- Note:
It is good to consider the other goals when evaluating terms.
For example, consider the constraints:
P (x * inf), x >= 1
We cannot simplify `x * inf` on its own, because we do not know if `x`
might be 0. However, in the contxt of `x >= 1`, we know that this is
impossible, and we can simplify the constraints to:
P inf, x >= 1
However, we should be careful to avoid circular reasoning, as we wouldn't
want to use the fact that `x >= 1` to simplify `x >= 1` to true.
-}
-- XXX: currently simplify individually
simplifyConstraintTerms :: Num.Solver -> [Goal] -> IO [Goal]
simplifyConstraintTerms s gs =
debugBlock s "Simplifying terms" $ return (map simpGoal gs)
where simpGoal g = g { goal = simpProp (goal g) }
solveConstraints :: Num.Solver ->
[Goal] {- We may use these, but don't try to solve,
we already tried and failed. -} ->
[Goal] {- Need to solve these -} ->
IO (Either [Goal] [Goal])
-- ^ Left: contradiciting goals,
-- Right: goals that were not solved, or sub-goals
-- for solved goals. Does not include "old"
solveConstraints s otherGs gs0 =
debugBlock s "Solving constraints" $ solveClassCts [] [] gs0
where
otherNumerics = [ g | Right g <- map Num.numericRight otherGs ]
solveClassCts unsolvedClass numerics [] =
do unsolvedNum <- solveNumerics s otherNumerics numerics
return (Right (unsolvedClass ++ unsolvedNum))
solveClassCts unsolved numerics (g : gs) =
case Num.numericRight g of
Right n -> solveClassCts unsolved (n : numerics) gs
Left c ->
case classStep c of
Unsolvable -> return (Left [g])
Unsolved -> solveClassCts (g : unsolved) numerics gs
Solved Nothing subs -> solveClassCts unsolved numerics (subs ++ gs)
Solved (Just su) _ -> panic "solveClassCts"
[ "Unexpected substituion", show su ]
solveNumerics :: Num.Solver ->
[(Goal,Num.Prop)] {- ^ Consult these -} ->
[(Goal,Num.Prop)] {- ^ Solve these -} ->
IO [Goal]
solveNumerics s consultGs solveGs =
Num.withScope s $
do _ <- Num.assumeProps s (map (goal . fst) consultGs)
Num.simplifyProps s (map Num.knownDefined solveGs)
computeImprovements :: Num.Solver -> [Goal] -> IO (Either [Goal] Subst)
computeImprovements s gs =
debugBlock s "Computing improvements" $
do let nums = [ g | Right g <- map Num.numericRight gs ]
res <- Num.withScope s $
do _ <- Num.assumeProps s (map (goal . fst) nums)
mb <- Num.check s
case mb of
Nothing -> return Nothing
Just (suish,_ps1) ->
do let (su,_ps2) = importSplitImps suish
-- Num.check has already checked that the intervals are sane,
-- so we don't need to check for a broken interval here
Right ints <- Num.getIntervals s
return (Just (ints,su))
case res of
Just (ints,su)
| isEmptySubst su
, (x,t) : _ <- mapMaybe (improveByDefn ints) gs ->
do let su' = singleSubst x t
debugLog s ("Improve by definition: " ++ show (pp su'))
return (Right su')
| otherwise -> return (Right su)
Nothing ->
do bad <- Num.minimizeContradictionSimpDef s
(map Num.knownDefined nums)
return (Left bad)
improveByDefn :: Map TVar Interval -> Goal -> Maybe (TVar,Type)
improveByDefn ints Goal { .. } =
do (var,ty) <- tryRewritePropAsSubst ints goal
return (var,simpType ty)
-- | Import an improving substitutin (i.e., a bunch of equations)
-- into a Cryptol substitution (which is idempotent).
-- The substitution will contain only unification variables.
-- "Improvements" on skolem variables become additional constraints.
importSplitImps :: Map Num.Name Num.Expr -> (Subst, [Prop])
importSplitImps = mk . partitionEithers . map imp . Map.toList
where
mk (uni,props) = (listSubst (catMaybes uni), props)
imp (x,e) = case (x, Num.importType e) of
(Num.UserName tv, Just ty) ->
case tv of
TVFree {} -> Left (Just (tv,ty))
TVBound {} -> Right (TVar tv =#= ty)
{- This may happen if we are working on an implication,
and we have an improvement about a variable in the
assumptions that is not in any og the goals.
XXX: Perhaps, we should mark these variable, so we don't waste
time to "improve" them. -}
_ -> Left Nothing
-- | Import an improving substitution into a Cryptol substitution.
-- The substitution will contain both unification and skolem variables,
-- so this should be used when processing *givens*.
importImps :: Map Num.Name Num.Expr -> Subst
importImps = listSubst . map imp . Map.toList
where
imp (x,e) = case (x, Num.importType e) of
(Num.UserName tv, Just ty) -> (tv,ty)
_ -> panic "importImps" [ "Failed to import:", show x, show e ]
importSideConds :: [Num.Prop] -> ([Goal],[Num.Prop])
importSideConds = go [] []
where
go ok bad [] = ([ Goal CtImprovement emptyRange g | g <- ok], bad)
go ok bad (p:ps) = case Num.importProp p of
Just p' -> go (p' ++ ok) bad ps
Nothing -> go ok (p:bad) ps
--------------------------------------------------------------------------------
-- This is what we use to avoid ambiguity when generalizing.
{- If a variable, `a`, is:
1. Of kind KNum
2. Generic (i.e., does not appear in the environment)
3. It appears only in constraints but not in the resulting type
(i.e., it is not on the RHS of =>)
4. It (say, the variable 'a') appears only in constraints like this:
3.1 `a >= t` with (`a` not in `fvs t`)
3.2 in the `s` of `fin s`
Then we replace `a` with `max(t1 .. tn)` where the `ts`
are from the constraints `a >= t`.
If `t1 .. tn` is empty, then we replace `a` with 0.
This function assumes that 1-3 have been checked, and implements the rest.
So, given some variables and constraints that are about to be generalized,
we return:
1. a new (same or smaller) set of variables to quantify,
2. a new set of constraints,
3. a substitution which indicates what got defaulted.
-}
improveByDefaultingWith ::
Num.Solver ->
[TVar] -> -- candidates for defaulting
[Goal] -> -- constraints
IO ( [TVar] -- non-defaulted
, [Goal] -- new constraints
, Subst -- improvements from defaulting
, [Warning] -- warnings about defaulting
)
improveByDefaultingWith s as ps =
classify (Map.fromList [ (a,([],Set.empty)) | a <- as ]) [] [] ps
where
-- leq: candidate definitions (i.e. of the form x >= t, x `notElem` fvs t)
-- for each of these, we keep the list of `t`, and the free vars in them.
-- fins: all `fin` constraints
-- others: any other constraints
classify leqs fins others [] =
do let -- First, we use the `leqs` to choose some definitions.
(defs, newOthers) = select [] [] (fvs others) (Map.toList leqs)
su = listSubst defs
-- Do this to simplify the instantiated "fin" constraints.
(mb,su1) <- simpGoals' s (newOthers ++ others ++ apSubst su fins)
case mb of
Right gs1 ->
let warn (x,t) =
case x of
TVFree _ _ _ d -> DefaultingTo d t
TVBound {} -> panic "Crypto.TypeCheck.Infer"
[ "tryDefault attempted to default a quantified variable."
]
newSu = su1 @@ su -- XXX: is that right?
names = Set.fromList $ map fst $ fromMaybe [] $ substToList newSu
in return ( [ a | a <- as, not (a `Set.member` names) ]
, gs1
, newSu
, map warn defs
)
-- Something went wrong, don't default.
Left _ -> return (as,ps,su1 @@ su,[])
classify leqs fins others (prop : more) =
case tNoUser (goal prop) of
-- We found a `fin` constraint.
TCon (PC PFin) [ _ ] -> classify leqs (prop : fins) others more
-- Things of the form: x >= T(x) are not defaulted.
TCon (PC PGeq) [ TVar x, t ]
| x `elem` as && x `Set.notMember` freeRHS ->
classify leqs' fins others more
where freeRHS = fvs t
add (xs1,vs1) (xs2,vs2) = (xs1 ++ xs2, Set.union vs1 vs2)
leqs' = Map.insertWith add x ([(t,prop)],freeRHS) leqs
_ -> classify leqs fins (prop : others) more
-- Pickout which variables may be defaulted and how.
-- XXX: simpType t
select yes no _ [] = ([ (x, t) | (x,t) <- yes ] ,no)
select yes no otherFree ((x,(rhsG,vs)) : more) =
select newYes newNo newFree newMore
where
(ts,gs) = unzip rhsG
-- `x` selected only if appears nowehere else.
-- this includes other candidates for defaulting.
(newYes,newNo,newFree,newMore)
-- Mentioned in other constraints, definately not defaultable.
| x `Set.member` otherFree = noDefaulting
| otherwise =
let deps = [ y | (y,(_,yvs)) <- more, x `Set.member` yvs ]
recs = filter (`Set.member` vs) deps
in if not (null recs) || isBoundTV x -- x >= S(y), y >= T(x)
then noDefaulting
-- x >= S, y >= T(x) or
-- x >= S(y), y >= S
else yesDefaulting
where
noDefaulting = ( yes, gs ++ no, vs `Set.union` otherFree, more )
yesDefaulting =
let ty = case ts of
[] -> tNum (0::Int)
_ -> foldr1 tMax ts
su1 = singleSubst x ty
in ( (x,ty) : [ (y,apSubst su1 t) | (y,t) <- yes ]
, no -- We know that `x` does not appear here
, otherFree -- We know that `x` did not appear here either
-- No need to update the `vs` because we've already
-- checked that there are no recursive dependencies.
, [ (y, (apSubst su1 ts1, vs1)) | (y,(ts1,vs1)) <- more ]
)
-- | Try to pick a reasonable instantiation for an expression, with
-- the given type. This is useful when we do evaluation at the REPL.
-- The resulting types should satisfy the constraints of the schema.
defaultReplExpr :: Num.Solver -> Expr -> Schema
-> IO (Maybe ([(TParam,Type)], Expr))
defaultReplExpr so e s =
if all (\v -> kindOf v == KNum) (sVars s)
then do let params = map tpVar (sVars s)
mbSubst <- tryGetModel so params (sProps s)
case mbSubst of
Just su ->
do (res,su1) <- simpGoals' so (map (makeGoal su) (sProps s))
return $
case res of
Right [] | isEmptySubst su1 ->
do tys <- mapM (bindParam su) params
return (zip (sVars s) tys, appExpr tys)
_ -> Nothing
_ -> return Nothing
else return Nothing
where
makeGoal su p = Goal { goalSource = error "goal source"
, goalRange = error "goal range"
, goal = apSubst su p
}
bindParam su tp =
do let ty = TVar tp
ty' = apSubst su ty
guard (ty /= ty')
return ty'
appExpr tys = foldl (\e1 _ -> EProofApp e1) (foldl ETApp e tys) (sProps s)
-- | Attempt to default the given constraints by asserting them in the SMT
-- solver, and asking it for a model.
tryGetModel ::
Num.Solver ->
[TVar] -> -- variables to try defaulting
[Prop] -> -- constraints
IO (Maybe Subst)
tryGetModel s xs ps =
-- We are only interested in finite instantiations
Num.getModel s (map (pFin . TVar) xs ++ ps)
--------------------------------------------------------------------------------
simpType :: Type -> Type
simpType ty = fromMaybe ty (simpTypeMaybe ty)
simpProp :: Prop -> Prop
simpProp p = case p of
TUser f ts q -> TUser f (map simpType ts) (simpProp q)
TCon c ts -> TCon c (map simpType ts)
TVar {} -> panic "simpProp" ["variable", show p]
TRec {} -> panic "simpProp" ["record", show p]
simpTypeMaybe :: Type -> Maybe Type
simpTypeMaybe ty =
case ty of
TCon c ts ->
case c of
TF {} -> do e <- Num.exportType ty
e1 <- Num.crySimpExprMaybe e
Num.importType e1
_ -> TCon c `fmap` anyJust simpTypeMaybe ts
TVar _ -> Nothing
TUser x ts t -> TUser x ts `fmap` simpTypeMaybe t
TRec fs ->
do let (ls,ts) = unzip fs
ts' <- anyJust simpTypeMaybe ts
return (TRec (zip ls ts'))
--------------------------------------------------------------------------------
_testSimpGoals :: IO ()
_testSimpGoals = Num.withSolver cfg $ \s ->
do mapM_ dump asmps
mapM_ (dump .goal) gs
_ <- Num.assumeProps s asmps
_mbImps <- Num.check s
(mb,_) <- simpGoals' s gs
case mb of
Right _ -> debugLog s "End of test"
Left _ -> debugLog s "Impossible"
where
cfg = SolverConfig { solverPath = "z3"
, solverArgs = [ "-smt2", "-in" ]
, solverVerbose = 1
}
asmps = []
gs = map fakeGoal [ tv 0 =#= tMin (num 10) (tv 1)
, tv 1 =#= num 10
]
fakeGoal p = Goal { goalSource = undefined, goalRange = undefined, goal = p }
tv n = TVar (TVFree n KNum Set.empty (text "test var"))
_btv n = TVar (TVBound n KNum)
num x = tNum (x :: Int)
dump a = do putStrLn "-------------------_"
case Num.exportProp a of
Just b -> do print $ Num.ppProp' $ Num.propToProp' b
putStrLn "-------------------"
Nothing -> print "can't export"
cryptol-2.4.0/src/Cryptol/TypeCheck/Subst.hs 0000644 0000000 0000000 00000021542 12737220176 017150 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Subst where
import Data.Either (partitionEithers)
import qualified Data.Map.Strict as Map
import qualified Data.IntMap as IntMap
import Data.Set (Set)
import qualified Data.Set as Set
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.PP
import Cryptol.TypeCheck.TypeMap
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.Misc(anyJust)
data Subst = S { suMap :: !(Map.Map TVar Type)
, suDefaulting :: !Bool
}
deriving Show
emptySubst :: Subst
emptySubst = S { suMap = Map.empty, suDefaulting = False }
singleSubst :: TVar -> Type -> Subst
singleSubst x t = S { suMap = Map.singleton x t, suDefaulting = False }
(@@) :: Subst -> Subst -> Subst
s2 @@ s1 | Map.null (suMap s2) =
if (suDefaulting s1 || not (suDefaulting s2)) then
s1
else
s1{ suDefaulting = True }
s2 @@ s1 = S { suMap = Map.map (apSubst s2) (suMap s1) `Map.union` suMap s2
, suDefaulting = suDefaulting s1 || suDefaulting s2
}
defaultingSubst :: Subst -> Subst
defaultingSubst s = s { suDefaulting = True }
-- | Makes a substitution out of a list.
-- WARNING: We do not validate the list in any way, so the caller should
-- ensure that we end up with a valid (e.g., idempotent) substitution.
listSubst :: [(TVar,Type)] -> Subst
listSubst xs = S { suMap = Map.fromList xs, suDefaulting = False }
isEmptySubst :: Subst -> Bool
isEmptySubst su = Map.null (suMap su)
-- Returns `Nothing` if this is a deaulting substitution
substToList :: Subst -> Maybe [ (TVar, Type) ]
substToList su | suDefaulting su = Nothing
| otherwise = Just $ Map.toList $ suMap su
instance PP (WithNames Subst) where
ppPrec _ (WithNames s mp)
| null els = text "(empty substitution)"
| otherwise = text "Substitution:" $$ nest 2 (vcat (map pp1 els))
where pp1 (x,t) = ppWithNames mp x <+> text "=" <+> ppWithNames mp t
els = Map.toList (suMap s)
instance PP Subst where
ppPrec n = ppWithNamesPrec IntMap.empty n
class FVS t where
fvs :: t -> Set TVar
instance FVS Type where
fvs = go
where
go ty =
case ty of
TCon _ ts -> Set.unions (map go ts)
TVar x -> Set.singleton x
TUser _ _ t -> go t
TRec fs -> Set.unions (map (go . snd) fs)
instance FVS a => FVS [a] where
fvs xs = Set.unions (map fvs xs)
instance (FVS a, FVS b) => FVS (a,b) where
fvs (x,y) = Set.union (fvs x) (fvs y)
instance FVS Schema where
fvs (Forall as ps t) =
Set.difference (Set.union (fvs ps) (fvs t)) bound
where bound = Set.fromList (map tpVar as)
-- | Apply a substitution. Returns `Nothing` if nothing changed.
apSubstMaybe :: Subst -> Type -> Maybe Type
apSubstMaybe su ty =
case ty of
TCon t ts -> TCon t `fmap` anyJust (apSubstMaybe su) ts
TUser f ts t -> do t1 <- apSubstMaybe su t
return (TUser f (map (apSubst su) ts) t1)
TRec fs -> TRec `fmap` anyJust fld fs
where fld (x,t) = do t1 <- apSubstMaybe su t
return (x,t1)
TVar x ->
case Map.lookup x (suMap su) of
Just t -> Just $ if suDefaulting su
then apSubst (defaultingSubst emptySubst) t
else t
Nothing -> if suDefaulting su
then Just (defaultFreeVar x)
else Nothing
class TVars t where
apSubst :: Subst -> t -> t -- ^ replaces free vars
instance TVars t => TVars (Maybe t) where
apSubst s = fmap (apSubst s)
instance TVars t => TVars [t] where
apSubst s = map (apSubst s)
instance (TVars s, TVars t) => TVars (s,t) where
apSubst s (x,y) = (apSubst s x, apSubst s y)
instance TVars Type where
apSubst su ty =
case ty of
TCon t ts -> TCon t (apSubst su ts)
TUser f ts t -> TUser f (apSubst su ts) (apSubst su t)
TRec fs -> TRec [ (x,apSubst su s) | (x,s) <- fs ]
TVar x
| Just t <- Map.lookup x (suMap su) ->
if suDefaulting su
then apSubst (defaultingSubst emptySubst) t
else t
| suDefaulting su -> defaultFreeVar x
| otherwise -> ty
-- | Pick types for unconstrained unification variables.
defaultFreeVar :: TVar -> Type
defaultFreeVar x@(TVBound {}) = TVar x
defaultFreeVar (TVFree _ k _ d) =
case k of
KType -> tBit
KNum -> tNum (0 :: Int)
_ -> panic "Cryptol.TypeCheck.Subst.defaultFreeVar"
[ "Free variable of unexpected kind."
, "Source: " ++ show d
, "Kind: " ++ show (pp k) ]
instance (Functor m, TVars a) => TVars (List m a) where
apSubst su = fmap (apSubst su)
instance TVars a => TVars (TypeMap a) where
apSubst su = fmap (apSubst su)
-- | Apply the substitution to the keys of a type map.
apSubstTypeMapKeys :: Subst -> TypeMap a -> TypeMap a
apSubstTypeMapKeys su = go (\_ x -> x) id
where
go :: (a -> a -> a) -> (a -> a) -> TypeMap a -> TypeMap a
go merge atNode TM { .. } = foldl addKey tm' tys
where
addKey tm (ty,a) = insertWithTM merge ty a tm
tm' = TM { tvar = Map.fromList vars
, tcon = fmap (lgo merge atNode) tcon
, trec = fmap (lgo merge atNode) trec
}
-- partition out variables that have been replaced with more specific types
(vars,tys) = partitionEithers
[ case Map.lookup v (suMap su) of
Just ty -> Right (ty,a')
Nothing -> Left (v, a')
| (v,a) <- Map.toList tvar
, let a' = atNode a
]
lgo :: (a -> a -> a) -> (a -> a) -> List TypeMap a -> List TypeMap a
lgo merge atNode k = k { nil = fmap atNode (nil k)
, cons = go (unionTM merge)
(lgo merge atNode)
(cons k)
}
{- | WARNING: This instance assumes that the quantified variables in the
types in the substitution will not get captured by the quantified variables.
This is reasonable because there should be no shadowing of quantified
variables but, just in case, we make a sanity check and panic if somehow
capture did occur. -}
instance TVars Schema where
apSubst su sch@(Forall xs ps t)
| Set.null captured = Forall xs (apSubst su1 ps) (apSubst su1 t)
| otherwise = panic "Cryptol.TypeCheck.Subst.apSubst (Schema)"
[ "Captured quantified variables:"
, "Substitution: " ++ show (brackets (commaSep (map ppBinding $ Map.toList m1)))
, "Schema: " ++ show (pp sch)
, "Variables: " ++ show (commaSep (map pp (Set.toList captured)))
]
where
ppBinding (v,x) = pp v <+> text ":=" <+> pp x
used = fvs sch
m1 = Map.filterWithKey (\k _ -> k `Set.member` used) (suMap su)
su1 = S { suMap = m1, suDefaulting = suDefaulting su }
captured = Set.fromList (map tpVar xs) `Set.intersection`
fvs (Map.elems m1)
instance TVars Expr where
apSubst su = go
where
go expr =
case expr of
EApp e1 e2 -> EApp (go e1) (go e2)
EAbs x t e1 -> EAbs x (apSubst su t) (go e1)
ETAbs a e -> ETAbs a (go e)
ETApp e t -> ETApp (go e) (apSubst su t)
EProofAbs p e -> EProofAbs (apSubst su p) (go e)
EProofApp e -> EProofApp (go e)
ECast e t -> ECast (go e) (apSubst su t)
EVar {} -> expr
ETuple es -> ETuple (map go es)
ERec fs -> ERec [ (f, go e) | (f,e) <- fs ]
EList es t -> EList (map go es) (apSubst su t)
ESel e s -> ESel (go e) s
EComp t e mss -> EComp (apSubst su t) (go e) (apSubst su mss)
EIf e1 e2 e3 -> EIf (go e1) (go e2) (go e3)
EWhere e ds -> EWhere (go e) (apSubst su ds)
instance TVars Match where
apSubst su (From x t e) = From x (apSubst su t) (apSubst su e)
apSubst su (Let b) = Let (apSubst su b)
instance TVars DeclGroup where
apSubst su (NonRecursive d) = NonRecursive (apSubst su d)
apSubst su (Recursive ds) = Recursive (apSubst su ds)
instance TVars Decl where
apSubst su d = d { dSignature = apSubst su (dSignature d)
, dDefinition = apSubst su (dDefinition d)
}
instance TVars DeclDef where
apSubst su (DExpr e) = DExpr (apSubst su e)
apSubst _ DPrim = DPrim
instance TVars Module where
apSubst su m = m { mDecls = apSubst su (mDecls m) }
cryptol-2.4.0/src/Cryptol/TypeCheck/TypeMap.hs 0000644 0000000 0000000 00000013040 12737220176 017421 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances, FlexibleInstances #-}
{-# LANGUAGE DeriveFunctor #-}
module Cryptol.TypeCheck.TypeMap
( TypeMap(..), TypesMap, TrieMap(..)
, insertTM, insertWithTM
, membersTM
, mapTM, mapWithKeyTM, mapMaybeTM
, List(..)
) where
import Cryptol.TypeCheck.AST
import Cryptol.Utils.Ident
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Maybe(fromMaybe,maybeToList)
import Control.Monad((<=<))
import Data.List(sortBy)
import Data.Maybe (isNothing)
import Data.Ord(comparing)
class TrieMap m k | m -> k where
emptyTM :: m a
nullTM :: m a -> Bool
lookupTM :: k -> m a -> Maybe a
alterTM :: k -> (Maybe a -> Maybe a) -> m a -> m a
unionTM :: (a -> a -> a) -> m a -> m a -> m a
toListTM :: m a -> [(k,a)]
mapMaybeWithKeyTM :: (k -> a -> Maybe b) -> m a -> m b
membersTM :: TrieMap m k => m a -> [a]
membersTM = map snd . toListTM
insertTM :: TrieMap m k => k -> a -> m a -> m a
insertTM t a = alterTM t (\_ -> Just a)
insertWithTM :: TrieMap m k => (a -> a -> a) -> k -> a -> m a -> m a
insertWithTM f t new = alterTM t $ \mb -> Just $ case mb of
Nothing -> new
Just old -> f old new
{-# INLINE mapTM #-}
mapTM :: TrieMap m k => (a -> b) -> m a -> m b
mapTM f = mapMaybeWithKeyTM (\ _ a -> Just (f a))
{-# INLINE mapWithKeyTM #-}
mapWithKeyTM :: TrieMap m k => (k -> a -> b) -> m a -> m b
mapWithKeyTM f = mapMaybeWithKeyTM (\ k a -> Just (f k a))
{-# INLINE mapMaybeTM #-}
mapMaybeTM :: TrieMap m k => (a -> Maybe b) -> m a -> m b
mapMaybeTM f = mapMaybeWithKeyTM (\_ -> f)
data List m a = L { nil :: Maybe a
, cons :: m (List m a)
} deriving (Functor)
instance TrieMap m a => TrieMap (List m) [a] where
emptyTM = L { nil = Nothing, cons = emptyTM }
nullTM k = isNothing (nil k) && nullTM (cons k)
lookupTM k =
case k of
[] -> nil
x : xs -> lookupTM xs <=< lookupTM x . cons
alterTM k f m =
case k of
[] -> m { nil = f (nil m) }
x:xs -> m { cons = alterTM x (updSub xs f) (cons m) }
toListTM m =
[ ([], v) | v <- maybeToList (nil m) ] ++
[ (x:xs,v) | (x,m1) <- toListTM (cons m), (xs,v) <- toListTM m1 ]
unionTM f m1 m2 = L { nil = case (nil m1, nil m2) of
(Just x, Just y) -> Just (f x y)
(Just x, _) -> Just x
(_, Just y) -> Just y
_ -> Nothing
, cons = unionTM (unionTM f) (cons m1) (cons m2)
}
mapMaybeWithKeyTM f = go []
where
go acc l = L { nil = f (reverse acc) =<< nil l
, cons = mapMaybeWithKeyTM (\k a -> Just (go (k:acc) a)) (cons l)
}
instance Ord a => TrieMap (Map a) a where
emptyTM = Map.empty
nullTM = Map.null
lookupTM = Map.lookup
alterTM = flip Map.alter
toListTM = Map.toList
unionTM = Map.unionWith
mapMaybeWithKeyTM = Map.mapMaybeWithKey
type TypesMap = List TypeMap
data TypeMap a = TM { tvar :: Map TVar a
, tcon :: Map TCon (List TypeMap a)
, trec :: Map [Ident] (List TypeMap a)
} deriving (Functor)
instance TrieMap TypeMap Type where
emptyTM = TM { tvar = emptyTM, tcon = emptyTM, trec = emptyTM }
nullTM ty = and [ nullTM (tvar ty)
, nullTM (tcon ty)
, nullTM (trec ty) ]
lookupTM ty =
case ty of
TUser _ _ t -> lookupTM t
TVar x -> lookupTM x . tvar
TCon c ts -> lookupTM ts <=< lookupTM c . tcon
TRec fs -> let (xs,ts) = unzip $ sortBy (comparing fst) fs
in lookupTM ts <=< lookupTM xs . trec
alterTM ty f m =
case ty of
TUser _ _ t -> alterTM t f m
TVar x -> m { tvar = alterTM x f (tvar m) }
TCon c ts -> m { tcon = alterTM c (updSub ts f) (tcon m) }
TRec fs -> let (xs,ts) = unzip $ sortBy (comparing fst) fs
in m { trec = alterTM xs (updSub ts f) (trec m) }
toListTM m =
[ (TVar x, v) | (x,v) <- toListTM (tvar m) ] ++
[ (TCon c ts, v) | (c,m1) <- toListTM (tcon m)
, (ts,v) <- toListTM m1 ] ++
[ (TRec (zip fs ts), v) | (fs,m1) <- toListTM (trec m)
, (ts,v) <- toListTM m1 ]
unionTM f m1 m2 = TM { tvar = unionTM f (tvar m1) (tvar m2)
, tcon = unionTM (unionTM f) (tcon m1) (tcon m2)
, trec = unionTM (unionTM f) (trec m1) (trec m2)
}
mapMaybeWithKeyTM f m =
TM { tvar = mapMaybeWithKeyTM (\v -> f (TVar v)) (tvar m)
, tcon = mapWithKeyTM (\c l -> mapMaybeWithKeyTM
(\ts a -> f (TCon c ts) a) l) (tcon m)
, trec = mapWithKeyTM (\fs l -> mapMaybeWithKeyTM
(\ts a -> f (TRec (zip fs ts)) a) l) (trec m)
}
updSub :: TrieMap m k => k -> (Maybe a -> Maybe a) -> Maybe (m a) -> Maybe (m a)
updSub k f = Just . alterTM k f . fromMaybe emptyTM
instance Show a => Show (TypeMap a) where
showsPrec p xs = showsPrec p (toListTM xs)
cryptol-2.4.0/src/Cryptol/TypeCheck/TypeOf.hs 0000644 0000000 0000000 00000011210 12737220176 017245 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.TypeCheck.TypeOf
( fastTypeOf
, fastSchemaOf
) where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst
import Cryptol.Utils.Panic
import Cryptol.Utils.PP
import Data.Map (Map)
import qualified Data.Map as Map
-- | Given a typing environment and an expression, compute the type of
-- the expression as quickly as possible, assuming that the expression
-- is well formed with correct type annotations.
fastTypeOf :: Map Name Schema -> Expr -> Type
fastTypeOf tyenv expr =
case expr of
-- Monomorphic fragment
EList es t -> tSeq (tNum (length es)) t
ETuple es -> tTuple (map (fastTypeOf tyenv) es)
ERec fields -> tRec [ (name, fastTypeOf tyenv e) | (name, e) <- fields ]
ESel e sel -> typeSelect (fastTypeOf tyenv e) sel
EIf _ e _ -> fastTypeOf tyenv e
EComp t _ _ -> t
EAbs x t e -> tFun t (fastTypeOf (Map.insert x (Forall [] [] t) tyenv) e)
EApp e _ -> case tIsFun (fastTypeOf tyenv e) of
Just (_, t) -> t
Nothing -> panic "Cryptol.TypeCheck.TypeOf.fastTypeOf"
[ "EApp with non-function operator" ]
ECast _ t -> t
-- Polymorphic fragment
EVar {} -> polymorphic
ETAbs {} -> polymorphic
ETApp {} -> polymorphic
EProofAbs {} -> polymorphic
EProofApp {} -> polymorphic
EWhere {} -> polymorphic
where
polymorphic =
case fastSchemaOf tyenv expr of
Forall [] [] ty -> ty
_ -> panic "Cryptol.TypeCheck.TypeOf.fastTypeOf"
[ "unexpected polymorphic type" ]
fastSchemaOf :: Map Name Schema -> Expr -> Schema
fastSchemaOf tyenv expr =
case expr of
-- Polymorphic fragment
EVar x -> case Map.lookup x tyenv of
Just ty -> ty
Nothing -> panic "Cryptol.TypeCheck.TypeOf.fastSchemaOf"
[ "EVar failed to find type variable:", show x ]
ETAbs tparam e -> case fastSchemaOf tyenv e of
Forall tparams props ty -> Forall (tparam : tparams) props ty
ETApp e t -> case fastSchemaOf tyenv e of
Forall (tparam : tparams) props ty -> Forall tparams (apSubst s props) (apSubst s ty)
where s = singleSubst (tpVar tparam) t
_ -> panic "Cryptol.TypeCheck.TypeOf.fastSchemaOf"
[ "ETApp body with no type parameters" ]
EProofAbs p e -> case fastSchemaOf tyenv e of
Forall [] props ty -> Forall [] (p : props) ty
_ -> panic "Cryptol.TypeCheck.TypeOf.fastSchemaOf"
[ "EProofAbs with polymorphic expression" ]
EProofApp e -> case fastSchemaOf tyenv e of
Forall [] (_ : props) ty -> Forall [] props ty
_ -> panic "Cryptol.TypeCheck.TypeOf.fastSchemaOf"
[ "EProofApp with polymorphic expression or"
, "no props in scope"
]
EWhere e dgs -> fastSchemaOf (foldr addDeclGroup tyenv dgs) e
where addDeclGroup (Recursive ds) = flip (foldr addDecl) ds
addDeclGroup (NonRecursive d) = addDecl d
addDecl d = Map.insert (dName d) (dSignature d)
-- Monomorphic fragment
EList {} -> monomorphic
ETuple {} -> monomorphic
ERec {} -> monomorphic
ESel {} -> monomorphic
EIf {} -> monomorphic
EComp {} -> monomorphic
EApp {} -> monomorphic
EAbs {} -> monomorphic
ECast {} -> monomorphic
where
monomorphic = Forall [] [] (fastTypeOf tyenv expr)
-- | Yields the return type of the selector on the given argument type.
typeSelect :: Type -> Selector -> Type
typeSelect (TUser _ _ ty) sel = typeSelect ty sel
typeSelect (TCon _tctuple ts) (TupleSel i _) = ts !! i
typeSelect (TRec fields) (RecordSel n _)
| Just ty <- lookup n fields = ty
typeSelect (TCon _tcseq [_, a]) (ListSel _ _) = a
typeSelect ty _ = panic "Cryptol.TypeCheck.TypeOf.typeSelect"
[ "cannot apply selector to value of type", render (pp ty) ]
cryptol-2.4.0/src/Cryptol/TypeCheck/Unify.hs 0000644 0000000 0000000 00000007031 12737220176 017137 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE PatternGuards, ViewPatterns #-}
{-# LANGUAGE DeriveFunctor #-}
module Cryptol.TypeCheck.Unify where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst
import Cryptol.Utils.Panic (panic)
import Data.Ord(comparing)
import Data.List(sortBy)
import qualified Data.Set as Set
import Prelude ()
import Prelude.Compat
-- | The most general unifier is a substitution and a set of constraints
-- on bound variables.
type MGU = (Subst,[Prop])
data Result a = OK a | Error UnificationError
deriving (Functor)
data UnificationError
= UniTypeMismatch Type Type
| UniKindMismatch Kind Kind
| UniTypeLenMismatch Int Int
| UniRecursive TVar Type
| UniNonPolyDepends TVar [TVar]
| UniNonPoly TVar Type
instance Applicative Result where
pure = OK
OK f <*> OK x = OK (f x)
OK _ <*> Error e = Error e
Error e <*> _ = Error e
instance Monad Result where
return a = OK a
OK a >>= k = k a
Error x >>= _ = Error x
fail x = panic "Cryptol.TypeCheck.Unify.fail" [x]
uniError :: UnificationError -> Result a
uniError e = Error e
emptyMGU :: MGU
emptyMGU = (emptySubst, [])
mgu :: Type -> Type -> Result MGU
mgu (TUser c1 ts1 _) (TUser c2 ts2 _)
| c1 == c2 && ts1 == ts2 = return emptyMGU
mgu (TVar x) t = bindVar x t
mgu t (TVar x) = bindVar x t
mgu (TUser _ _ t1) t2 = mgu t1 t2
mgu t1 (TUser _ _ t2) = mgu t1 t2
mgu (TCon (TC tc1) ts1) (TCon (TC tc2) ts2)
| tc1 == tc2 = mguMany ts1 ts2
mgu (TCon (TF f1) ts1) (TCon (TF f2) ts2)
| f1 == f2 && ts1 == ts2 = return emptyMGU
mgu t1 t2
| TCon (TF _) _ <- t1, isNum, k1 == k2 = return (emptySubst, [t1 =#= t2])
| TCon (TF _) _ <- t2, isNum, k1 == k2 = return (emptySubst, [t1 =#= t2])
where
k1 = kindOf t1
k2 = kindOf t2
isNum = k1 == KNum
mgu (TRec fs1) (TRec fs2)
| ns1 == ns2 = mguMany ts1 ts2
where
(ns1,ts1) = sortFields fs1
(ns2,ts2) = sortFields fs2
sortFields = unzip . sortBy (comparing fst)
mgu t1 t2
| not (k1 == k2) = uniError $ UniKindMismatch k1 k2
| otherwise = uniError $ UniTypeMismatch t1 t2
where
k1 = kindOf t1
k2 = kindOf t2
mguMany :: [Type] -> [Type] -> Result MGU
mguMany [] [] = return emptyMGU
mguMany (t1 : ts1) (t2 : ts2) =
do (su1,ps1) <- mgu t1 t2
(su2,ps2) <- mguMany (apSubst su1 ts1) (apSubst su1 ts2)
return (su2 @@ su1, ps1 ++ ps2)
mguMany t1 t2 = uniError $ UniTypeLenMismatch (length t1) (length t2)
bindVar :: TVar -> Type -> Result MGU
bindVar x (tNoUser -> TVar y)
| x == y = return emptyMGU
bindVar v@(TVBound {}) (tNoUser -> TVar v1@(TVFree {})) = bindVar v1 (TVar v)
bindVar v@(TVBound _ k) t
| k == kindOf t = if k == KNum
then return (emptySubst, [TVar v =#= t])
else uniError $ UniNonPoly v t
| otherwise = uniError $ UniKindMismatch k (kindOf t)
bindVar x@(TVFree _ k inScope _d) t
| not (k == kindOf t) = uniError $ UniKindMismatch k (kindOf t)
| recTy && k == KType = uniError $ UniRecursive x t
| not (Set.null escaped) = uniError $ UniNonPolyDepends x$ Set.toList escaped
| recTy = return (emptySubst, [TVar x =#= t])
| otherwise = return (singleSubst x t, [])
where
vs = fvs t
escaped = Set.filter isBoundTV vs `Set.difference` inScope
recTy = x `Set.member` vs
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/ 0000755 0000000 0000000 00000000000 12737220176 016762 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Class.hs 0000644 0000000 0000000 00000007134 12737220176 020370 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Solving class constraints.
{-# LANGUAGE PatternGuards #-}
module Cryptol.TypeCheck.Solver.Class
( classStep
, expandProp
) where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.InferTypes(Goal(..), Solved(..))
-- | Solve class constraints.
-- If not, then we return 'Nothing'.
-- If solved, ther we return 'Just' a list of sub-goals.
classStep :: Goal -> Solved
classStep g = case goal g of
TCon (PC PArith) [ty] -> solveArithInst g (tNoUser ty)
TCon (PC PCmp) [ty] -> solveCmpInst g (tNoUser ty)
_ -> Unsolved
-- | Solve an original goal in terms of the give sub-goals.
solved :: Goal -> [Prop] -> Solved
solved g ps = Solved Nothing [ g { goal = p } | p <- ps ]
-- | Solve an Arith constraint by instance, if possible.
solveArithInst :: Goal -> Type -> Solved
solveArithInst g ty = case ty of
-- Arith [n]e
TCon (TC TCSeq) [n, e] -> solveArithSeq g n e
-- Arith b => Arith (a -> b)
TCon (TC TCFun) [_,b] -> solved g [ pArith b ]
-- (Arith a, Arith b) => Arith (a,b)
TCon (TC (TCTuple _)) es -> solved g [ pArith e | e <- es ]
-- Arith Bit fails
TCon (TC TCBit) [] -> Unsolvable
-- (Arith a, Arith b) => Arith { x1 : a, x2 : b }
TRec fs -> solved g [ pArith ety | (_,ety) <- fs ]
_ -> Unsolved
-- | Solve an Arith constraint for a sequence. The type passed here is the
-- element type of the sequence.
solveArithSeq :: Goal -> Type -> Type -> Solved
solveArithSeq g n ty = case ty of
-- fin n => Arith [n]Bit
TCon (TC TCBit) [] -> solved g [ pFin n ]
-- variables are not solvable.
TVar {} -> Unsolved
-- Arith ty => Arith [n]ty
_ -> solved g [ pArith ty ]
-- | Solve Cmp constraints.
solveCmpInst :: Goal -> Type -> Solved
solveCmpInst g ty = case ty of
-- Cmp Bit
TCon (TC TCBit) [] -> solved g []
-- (fin n, Cmp a) => Cmp [n]a
TCon (TC TCSeq) [n,a] -> solved g [ pFin n, pCmp a ]
-- (Cmp a, Cmp b) => Cmp (a,b)
TCon (TC (TCTuple _)) es -> solved g (map pCmp es)
-- Cmp (a -> b) fails
TCon (TC TCFun) [_,_] -> Unsolvable
-- (Cmp a, Cmp b) => Cmp { x:a, y:b }
TRec fs -> solved g [ pCmp e | (_,e) <- fs ]
_ -> Unsolved
-- | Add propositions that are implied by the given one.
-- The result contains the orignal proposition, and maybe some more.
expandProp :: Prop -> [Prop]
expandProp prop =
prop :
case tNoUser prop of
TCon (PC pc) [ty] ->
case (pc, tNoUser ty) of
-- Arith [n]Bit => fin n
-- (Arith [n]a, a/=Bit) => Arith a
(PArith, TCon (TC TCSeq) [n,a])
| TCon (TC TCBit) _ <- ty1 -> [pFin n]
| TCon _ _ <- ty1 -> expandProp (pArith ty1)
| TRec {} <- ty1 -> expandProp (pArith ty1)
where
ty1 = tNoUser a
-- Arith (a -> b) => Arith b
(PArith, TCon (TC TCFun) [_,b]) -> expandProp (pArith b)
-- Arith (a,b) => (Arith a, Arith b)
(PArith, TCon (TC (TCTuple _)) ts) -> concatMap (expandProp . pArith) ts
-- Arith { x1 : a, x2 : b } => (Arith a, Arith b)
(PArith, TRec fs) -> concatMap (expandProp . pArith. snd) fs
-- Cmp [n]a => (fin n, Cmp a)
(PCmp, TCon (TC TCSeq) [n,a]) -> pFin n : expandProp (pCmp a)
-- Cmp (a,b) => (Cmp a, Cmp b)
(PCmp, TCon (TC (TCTuple _)) ts) -> concatMap (expandProp . pCmp) ts
-- Cmp { x:a, y:b } => (Cmp a, Cmp b)
(PCmp, TRec fs) -> concatMap (expandProp . pCmp . snd) fs
_ -> []
_ -> []
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/CrySAT.hs 0000644 0000000 0000000 00000053570 12737220176 020435 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Cryptol.TypeCheck.Solver.CrySAT
( withScope, withSolver
, assumeProps, simplifyProps, getModel
, check
, Solver, logger, getIntervals
, DefinedProp(..)
, debugBlock
, DebugLog(..)
, knownDefined, numericRight
, minimizeContradictionSimpDef
) where
import qualified Cryptol.TypeCheck.AST as Cry
import Cryptol.TypeCheck.InferTypes(Goal(..), SolverConfig(..), Solved(..))
import qualified Cryptol.TypeCheck.Subst as Cry
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.TypeCheck.Solver.Numeric.Fin
import Cryptol.TypeCheck.Solver.Numeric.ImportExport
import Cryptol.TypeCheck.Solver.Numeric.Interval
import Cryptol.TypeCheck.Solver.Numeric.Defined
import Cryptol.TypeCheck.Solver.Numeric.Simplify
import Cryptol.TypeCheck.Solver.Numeric.NonLin
import Cryptol.TypeCheck.Solver.Numeric.SMT
import Cryptol.Utils.PP -- ( Doc )
import Cryptol.Utils.Panic ( panic )
import MonadLib
import Data.Maybe ( fromMaybe )
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Foldable ( any, all )
import qualified Data.Set as Set
import Data.IORef ( IORef, newIORef, readIORef, modifyIORef',
atomicModifyIORef' )
import Prelude hiding (any,all)
import qualified SimpleSMT as SMT
-- | We use this to remember what we simplified
newtype SimpProp = SimpProp { unSimpProp :: Prop }
simpProp :: Prop -> SimpProp
simpProp p = SimpProp (crySimplify p)
class HasProp a where getProp :: a -> Cry.Prop
instance HasProp Cry.Prop where getProp = id
instance HasProp Goal where getProp = goal
-- | 'dpSimpProp' and 'dpSimpExprProp' should be logically equivalent,
-- to each other, and to whatever 'a' represents (usually 'a' is a 'Goal').
data DefinedProp a = DefinedProp
{ dpData :: a
-- ^ Optional data to associate with prop.
-- Often, the original `Goal` from which the prop was extracted.
, dpSimpProp :: SimpProp
{- ^ Fully simplified: may mention ORs, and named non-linear terms.
These are what we send to the prover, and we don't attempt to
convert them back into Cryptol types. -}
, dpSimpExprProp :: Prop
{- ^ A version of the proposition where just the expression terms
have been simplified. These should not contain ORs or named non-linear
terms because we want to import them back into Crytpol types. -}
}
knownDefined :: (a,Prop) -> DefinedProp a
knownDefined (a,p) = DefinedProp
{ dpData = a, dpSimpProp = simpProp p, dpSimpExprProp = p }
-- | Class goals go on the left, numeric goals go on the right.
numericRight :: Goal -> Either Goal (Goal, Prop)
numericRight g = case exportProp (goal g) of
Just p -> Right (g, p)
Nothing -> Left g
-- | Simplify a bunch of well-defined properties.
-- * Eliminates properties that are implied by the rest.
-- * Does not modify the set of assumptions.
simplifyProps :: Solver -> [DefinedProp Goal] -> IO [Goal]
simplifyProps s props =
debugBlock s "Simplifying properties" $
withScope s (go [] (eliminateSimpleGEQ props))
where
go survived [] = return survived
go survived (DefinedProp { dpSimpProp = SimpProp PTrue } : more) =
go survived more
go survived (p : more) =
case dpSimpProp p of
SimpProp PTrue -> go survived more
SimpProp p' ->
do mbProved <- withScope s $
do mapM_ (assert s) more
e <- getIntervals s
case e of
Left _ -> return Nothing
Right ints -> do b <- prove s p'
return (Just (ints,b))
case mbProved of
Just (_,True) -> go survived more
Just (ints,False) ->
debugLog s ("Using the fin solver:" ++ show (pp (goal (dpData p)))) >>
case cryIsFin ints (dpData p) of
Solved _ gs' ->
do debugLog s "solved"
let more' = [ knownDefined g | Right g <- map numericRight gs' ]
go survived (more' ++ more)
Unsolved ->
do debugLog s "unsolved"
assert s p
go (dpData p : survived) more
Unsolvable ->
do debugLog s "unsolvable"
go (dpData p:survived) more
Nothing -> go (dpData p:survived) more
{- | Simplify easy less-than-or-equal-to and equal-to goals.
Those are common with long lists of literals, so we have special handling
for them. In particular:
* Reduce goals of the form @(a >= k1, a >= k2, a >= k3, ...)@ to
@a >= max (k1, k2, k3, ...)@, when all the k's are constant.
* Eliminate goals of the form @ki >= k2@, when @k2@ is leq than @k1@.
* Eliminate goals of the form @a >= 0@.
NOTE: This assumes that the goals are well-defined.
-}
eliminateSimpleGEQ :: [DefinedProp a] -> [DefinedProp a]
eliminateSimpleGEQ = go Map.empty []
where
go geqs other (g : rest) =
case dpSimpExprProp g of
K a :== K b
| a == b -> go geqs other rest
_ :>= K (Nat 0) ->
go geqs other rest
K (Nat k1) :>= K (Nat k2)
| k1 >= k2 -> go geqs other rest
Var v :>= K (Nat k2) ->
go (addUpperBound v (k2,g) geqs) other rest
_ -> go geqs (g:other) rest
go geqs other [] = [ g | (_,g) <- Map.elems geqs ] ++ other
-- add in a possible upper bound for var
addUpperBound var g = Map.insertWith cmp var g
where
cmp a b | fst a > fst b = a
| otherwise = b
-- | Add the given constraints as assumptions.
-- * We assume that the constraints are well-defined.
-- * Modifies the set of assumptions.
assumeProps :: Solver -> [Cry.Prop] -> IO [SimpProp]
assumeProps s props =
do let ps = [ (p,p') | p <- props
, Just p' <- [exportProp p] ]
let defPs = [ (p,cryDefinedProp p') | (p,p') <- ps ]
let simpProps = map knownDefined (defPs ++ ps)
mapM_ (assert s) simpProps
return (map dpSimpProp simpProps)
-- XXX: Instead of asserting one at a time, perhaps we should
-- assert a conjunction. That way, we could simplify the whole thing
-- in one go, and would avoid having to assert 'true' many times.
-- | Given a list of propositions that together lead to a contradiction,
-- find a sub-set that still leads to a contradiction (but is smaller).
minimizeContradictionSimpDef :: HasProp a => Solver -> [DefinedProp a] -> IO [a]
minimizeContradictionSimpDef s ps = start [] ps
where
start bad todo =
do res <- SMT.check (solver s)
case res of
SMT.Unsat -> return (map dpData bad)
_ -> do solPush s
go bad [] todo
go _ _ [] = panic "minimizeContradiction"
$ ("No contradiction" : map (show . ppProp . dpSimpExprProp) ps)
go bad prev (d : more) =
do assert s d
res <- SMT.check (solver s)
case res of
SMT.Unsat -> do solPop s
assert s d
start (d : bad) prev
_ -> go bad (d : prev) more
{- | Attempt to find a substituion that, when applied, makes all of the
given properties hold. -}
getModel :: Solver -> [Cry.Prop] -> IO (Maybe Cry.Subst)
getModel s props = withScope s $
do ps <- assumeProps s props
res <- SMT.check (solver s)
let vars = Set.toList $ Set.unions $ map (cryPropFVS . unSimpProp) ps
case res of
SMT.Sat ->
do vs <- getVals (solver s) vars
-- This is guaranteed to be a model only for the *linear*
-- properties, so now we check if it works for the rest too.
let su1 = fmap K vs
ps1 = [ fromMaybe p (apSubst su1 p) | SimpProp p <- ps ]
ok p = case crySimplify p of
PTrue -> True
_ -> False
su2 = Cry.listSubst
[ (x, numTy v) | (UserName x, v) <- Map.toList vs ]
return (guard (all ok ps1) >> return su2)
_ -> return Nothing
where
numTy Inf = Cry.tInf
numTy (Nat k) = Cry.tNum k
--------------------------------------------------------------------------------
-- | An SMT solver, and some info about declared variables.
data Solver = Solver
{ solver :: SMT.Solver
-- ^ The actual solver
, declared :: IORef VarInfo
-- ^ Information about declared variables, and assumptions in scope.
, logger :: SMT.Logger
-- ^ For debugging
}
-- | Keeps track of declared variables and non-linear terms.
data VarInfo = VarInfo
{ curScope :: Scope
, otherScopes :: [Scope]
} deriving Show
data Scope = Scope
{ scopeNames :: [Name]
-- ^ Variables declared in this scope (not counting the ones from
-- previous scopes).
, scopeNonLinS :: NonLinS
{- ^ These are the non-linear terms mentioned in the assertions
that are currently asserted (including ones from previous scopes). -}
, scopeIntervals :: Either Cry.TVar (Map.Map Cry.TVar Interval)
-- ^ Either a type variable that makes the asserted properties unsatisfiable
-- (due to a broken interval), or the current set of intervals for type
-- variables. If a variable is not in the interval map, its value can be
-- anything.
--
-- This includes all intervals from previous scopes.
, scopeAsserted :: [Cry.Prop]
-- ^ This is the set of currently-asserted cryptol properties only in this
-- scope.
--
-- This includes all asserted props from previous scopes.
} deriving Show
scopeEmpty :: Scope
scopeEmpty = Scope { scopeNames = [], scopeNonLinS = initialNonLinS
, scopeIntervals = Right Map.empty, scopeAsserted = [] }
scopeElem :: Name -> Scope -> Bool
scopeElem x Scope { .. } = x `elem` scopeNames
scopeInsert :: Name -> Scope -> Scope
scopeInsert x Scope { .. } = Scope { scopeNames = x : scopeNames, .. }
scopeAssertNew :: Cry.Prop -> Scope -> Scope
scopeAssertNew prop Scope { .. } =
Scope { scopeIntervals = ints'
, scopeAsserted = props
, .. }
where
props = prop : scopeAsserted
ints' = case scopeIntervals of
Left tv -> Left tv
Right ints -> case computePropIntervals ints props of
NoChange -> scopeIntervals
NewIntervals is -> Right is
InvalidInterval tv -> Left tv
-- | Given a *simplified* prop, separate linear and non-linear parts
-- and return the linear ones.
scopeAssertSimpProp :: SimpProp -> Scope -> ([SimpProp],Scope)
scopeAssertSimpProp (SimpProp p) Scope { .. } =
let (ps1,s1) = nonLinProp scopeNonLinS p
in (map SimpProp ps1, Scope { scopeNonLinS = s1, .. })
scopeAssert :: HasProp a => DefinedProp a -> Scope -> ([SimpProp],Scope)
scopeAssert DefinedProp { .. } s =
let (ps1,s1) = scopeAssertSimpProp dpSimpProp s
in (ps1,scopeAssertNew (getProp dpData) s1)
-- | No scopes.
viEmpty :: VarInfo
viEmpty = VarInfo { curScope = scopeEmpty, otherScopes = [] }
-- | Check if a name is any of the scopes.
viElem :: Name -> VarInfo -> Bool
viElem x VarInfo { .. } = any (x `scopeElem`) (curScope : otherScopes)
-- | Add a name to a scope.
viInsert :: Name -> VarInfo -> VarInfo
viInsert x VarInfo { .. } = VarInfo { curScope = scopeInsert x curScope, .. }
-- | Add an assertion to the current scope. Returns the linear part.
viAssertSimpProp :: SimpProp -> VarInfo -> (VarInfo, [SimpProp])
viAssertSimpProp p VarInfo { .. } = ( VarInfo { curScope = s1, .. }, p1)
where (p1, s1) = scopeAssertSimpProp p curScope
viAssert :: HasProp a => DefinedProp a -> VarInfo -> (VarInfo, [SimpProp])
viAssert d VarInfo { .. } = (VarInfo { curScope = s1, .. },p1)
where (p1, s1) = scopeAssert d curScope
-- | Enter a scope.
viPush :: VarInfo -> VarInfo
viPush VarInfo { .. } =
VarInfo { curScope = scopeEmpty { scopeNonLinS = scopeNonLinS curScope
, scopeAsserted = scopeAsserted curScope
, scopeIntervals = scopeIntervals curScope }
, otherScopes = curScope : otherScopes
}
-- | Exit a scope.
viPop :: VarInfo -> VarInfo
viPop VarInfo { .. } = case otherScopes of
c : cs -> VarInfo { curScope = c, otherScopes = cs }
_ -> panic "viPop" ["no more scopes"]
-- | All declared names, that have not been "marked".
-- These are the variables whose values we are interested in.
viUnmarkedNames :: VarInfo -> [ Name ]
viUnmarkedNames VarInfo { .. } = concatMap scopeNames scopes
where scopes = curScope : otherScopes
getIntervals :: Solver -> IO (Either Cry.TVar (Map Cry.TVar Interval))
getIntervals Solver { .. } =
do vi <- readIORef declared
return (scopeIntervals (curScope vi))
-- | All known non-linear terms.
getNLSubst :: Solver -> IO Subst
getNLSubst Solver { .. } =
do VarInfo { .. } <- readIORef declared
return $ nonLinSubst $ scopeNonLinS curScope
-- | Execute a computation with a fresh solver instance.
withSolver :: SolverConfig -> (Solver -> IO a) -> IO a
withSolver SolverConfig { .. } k =
do logger <- if solverVerbose > 0 then SMT.newLogger 0 else return quietLogger
let smtDbg = if solverVerbose > 1 then Just logger else Nothing
solver <- SMT.newSolver solverPath solverArgs smtDbg
_ <- SMT.setOptionMaybe solver ":global-decls" "false"
SMT.setLogic solver "QF_LIA"
declared <- newIORef viEmpty
a <- k Solver { .. }
_ <- SMT.stop solver
return a
where
quietLogger = SMT.Logger { SMT.logMessage = \_ -> return ()
, SMT.logLevel = return 0
, SMT.logSetLevel= \_ -> return ()
, SMT.logTab = return ()
, SMT.logUntab = return ()
}
solPush :: Solver -> IO ()
solPush Solver { .. } =
do SMT.push solver
SMT.logTab logger
modifyIORef' declared viPush
solPop :: Solver -> IO ()
solPop Solver { .. } =
do modifyIORef' declared viPop
SMT.logUntab logger
SMT.pop solver
-- | Execute a computation in a new solver scope.
withScope :: Solver -> IO a -> IO a
withScope s k =
do solPush s
a <- k
solPop s
return a
-- | Declare a variable.
declareVar :: Solver -> Name -> IO ()
declareVar s@Solver { .. } a =
do done <- fmap (a `viElem`) (readIORef declared)
unless done $
do e <- SMT.declare solver (smtName a) SMT.tInt
let fin_a = smtFinName a
fin <- SMT.declare solver fin_a SMT.tBool
SMT.assert solver (SMT.geq e (SMT.int 0))
nlSu <- getNLSubst s
modifyIORef' declared (viInsert a)
case Map.lookup a nlSu of
Nothing -> return ()
Just e' ->
do let finDef = crySimplify (Fin e')
mapM_ (declareVar s) (Set.toList (cryPropFVS finDef))
SMT.assert solver $
SMT.eq fin (ifPropToSmtLib (desugarProp finDef))
-- | Add an assertion to the current context.
-- INVARIANT: Assertion is simplified.
assert :: HasProp a => Solver -> DefinedProp a -> IO ()
assert _ DefinedProp { dpSimpProp = SimpProp PTrue } = return ()
assert s@Solver { .. } def@DefinedProp { dpSimpProp = p } =
do debugLog s ("Assuming: " ++ show (ppProp (unSimpProp p)))
a <- getIntervals s
debugLog s ("Intervals before:" ++ show (either pp ppIntervals a))
ps1' <- atomicModifyIORef' declared (viAssert def)
b <- getIntervals s
debugLog s ("Intervals after:" ++ show (either pp ppIntervals b))
let ps1 = map unSimpProp ps1'
vs = Set.toList $ Set.unions $ map cryPropFVS ps1
mapM_ (declareVar s) vs
mapM_ (SMT.assert solver . ifPropToSmtLib . desugarProp) ps1
-- | Add an assertion to the current context.
-- INVARIANT: Assertion is simplified.
assertSimpProp :: Solver -> SimpProp -> IO ()
assertSimpProp _ (SimpProp PTrue) = return ()
assertSimpProp s@Solver { .. } p@(SimpProp p0) =
do debugLog s ("Assuming: " ++ show (ppProp p0))
ps1' <- atomicModifyIORef' declared (viAssertSimpProp p)
let ps1 = map unSimpProp ps1'
vs = Set.toList $ Set.unions $ map cryPropFVS ps1
mapM_ (declareVar s) vs
mapM_ (SMT.assert solver . ifPropToSmtLib . desugarProp) ps1
-- | Try to prove a property. The result is 'True' when we are sure that
-- the property holds, and 'False' otherwise. In other words, getting `False`
-- *does not* mean that the proposition does not hold.
prove :: Solver -> Prop -> IO Bool
prove _ PTrue = return True
prove s@Solver { .. } p =
debugBlock s ("Proving: " ++ show (ppProp p)) $
withScope s $
do assertSimpProp s (simpProp (Not p))
res <- SMT.check solver
case res of
SMT.Unsat -> debugLog s "Proved" >> return True
SMT.Unknown -> debugLog s "Not proved" >> return False -- We are not sure
SMT.Sat -> debugLog s "Not proved" >> return False
-- XXX: If the answer is Sat, it is possible that this is a
-- a fake example, as we need to evaluate the nonLinear constraints.
-- If they are all satisfied, then we have a genuine counter example.
-- Otherwise, we could look for another one...
{- | Check if the current set of assumptions is satisfiable, and find
some facts that must hold in any models of the current assumptions.
Returns `Nothing` if the currently asserted constraints are known to
be unsatisfiable.
Returns `Just (su, sub-goals)` is the current set is satisfiable.
* The `su` is a substitution that may be applied to the current constraint
set without loosing generality.
* The `sub-goals` are additional constraints that must hold if the
constraint set is to be satisfiable.
-}
check :: Solver -> IO (Maybe (Subst, [Prop]))
check s@Solver { .. } =
do e <- getIntervals s
case e of
Left tv ->
do debugLog s ("Invalid interval: " ++ show (pp tv))
return Nothing
Right ints ->
do debugLog s ("Intervals:" ++ show (ppIntervals ints))
res <- SMT.check solver
case res of
SMT.Unsat ->
do debugLog s "Not satisfiable"
return Nothing
SMT.Unknown ->
do debugLog s "Unknown"
return (Just (Map.empty, []))
SMT.Sat ->
do debugLog s "Satisfiable"
(impMap,sideConds) <- debugBlock s "Computing improvements"
(getImpSubst s)
return (Just (impMap, sideConds))
{- | Assuming that we are in a satisfiable state, try to compute an
improving substitution. We also return additional constraints that must
hold for the currently asserted propositions to hold.
-}
getImpSubst :: Solver -> IO (Subst,[Prop])
getImpSubst s@Solver { .. } =
do names <- viUnmarkedNames `fmap` readIORef declared
m <- getVals solver names
(impSu,sideConditions) <- cryImproveModel solver logger m
nlSu <- getNLSubst s
let isNonLinName (SysName {}) = True
isNonLinName (UserName {}) = False
(nlFacts, vFacts) = Map.partitionWithKey (\k _ -> isNonLinName k) impSu
(vV, vNL) = Map.partition noNLVars vFacts
nlSu1 = fmap (doAppSubst vV) nlSu
(vNL_su,vNL_eqs) = Map.partitionWithKey goodDef
$ fmap (doAppSubst nlSu1) vNL
nlSu2 = fmap (doAppSubst vNL_su) nlSu1
nlLkp x = case Map.lookup x nlSu2 of
Just e -> e
Nothing -> panic "getImpSubst"
[ "Missing NL variable:", show x ]
allSides =
[ Var a :== e | (a,e) <- Map.toList vNL_eqs ] ++
[ nlLkp x :== doAppSubst nlSu2 e | (x,e) <- Map.toList nlFacts ] ++
[ doAppSubst nlSu2 si | si <- sideConditions ]
theImpSu = composeSubst vNL_su vV
debugBlock s "Improvments" $
do debugBlock s "substitution" $
mapM_ (debugLog s . dump) (Map.toList theImpSu)
debugBlock s "side-conditions" $ debugLog s allSides
return (theImpSu, allSides)
where
goodDef k e = not (k `Set.member` cryExprFVS e)
isNLVar (SysName _) = True
isNLVar _ = False
noNLVars e = all (not . isNLVar) (cryExprFVS e)
dump (x,e) = show (ppProp (Var x :== e))
--------------------------------------------------------------------------------
debugBlock :: Solver -> String -> IO a -> IO a
debugBlock s@Solver { .. } name m =
do debugLog s name
SMT.logTab logger
a <- m
SMT.logUntab logger
return a
class DebugLog t where
debugLog :: Solver -> t -> IO ()
debugLogList :: Solver -> [t] -> IO ()
debugLogList s ts = case ts of
[] -> debugLog s "(none)"
_ -> mapM_ (debugLog s) ts
instance DebugLog Char where
debugLog s x = SMT.logMessage (logger s) (show x)
debugLogList s x = SMT.logMessage (logger s) x
instance DebugLog a => DebugLog [a] where
debugLog = debugLogList
instance DebugLog a => DebugLog (Maybe a) where
debugLog s x = case x of
Nothing -> debugLog s "(nothing)"
Just a -> debugLog s a
instance DebugLog Doc where
debugLog s x = debugLog s (show x)
instance DebugLog Cry.Type where
debugLog s x = debugLog s (pp x)
instance DebugLog Goal where
debugLog s x = debugLog s (goal x)
instance DebugLog Cry.Subst where
debugLog s x = debugLog s (pp x)
instance DebugLog Prop where
debugLog s x = debugLog s (ppProp x)
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/InfNat.hs 0000644 0000000 0000000 00000021160 12737220176 020475 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- This module defines natural numbers with an additional infinity
-- element, and various arithmetic operators on them.
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.TypeCheck.Solver.InfNat where
import Data.Bits
import Cryptol.Utils.Panic
import GHC.Generics (Generic)
import Control.DeepSeq
-- | Natural numbers with an infinity element
data Nat' = Nat Integer | Inf
deriving (Show, Eq, Ord, Generic, NFData)
fromNat :: Nat' -> Maybe Integer
fromNat n' =
case n' of
Nat i -> Just i
_ -> Nothing
--------------------------------------------------------------------------------
nEq :: Maybe Nat' -> Maybe Nat' -> Bool
nEq (Just x) (Just y) = x == y
nEq _ _ = False
nGt :: Maybe Nat' -> Maybe Nat' -> Bool
nGt (Just x) (Just y) = x > y
nGt _ _ = False
nFin :: Maybe Nat' -> Bool
nFin (Just x) = x /= Inf
nFin _ = False
--------------------------------------------------------------------------------
nAdd :: Nat' -> Nat' -> Nat'
nAdd Inf _ = Inf
nAdd _ Inf = Inf
nAdd (Nat x) (Nat y) = Nat (x + y)
{-| Some algebraic properties of interest:
> 1 * x = x
> x * (y * z) = (x * y) * z
> 0 * x = 0
> x * y = y * x
> x * (a + b) = x * a + x * b
-}
nMul :: Nat' -> Nat' -> Nat'
nMul (Nat 0) _ = Nat 0
nMul _ (Nat 0) = Nat 0
nMul Inf _ = Inf
nMul _ Inf = Inf
nMul (Nat x) (Nat y) = Nat (x * y)
{-| Some algebraic properties of interest:
> x ^ 0 = 1
> x ^ (n + 1) = x * (x ^ n)
> x ^ (m + n) = (x ^ m) * (x ^ n)
> x ^ (m * n) = (x ^ m) ^ n
-}
nExp :: Nat' -> Nat' -> Nat'
nExp _ (Nat 0) = Nat 1
nExp Inf _ = Inf
nExp (Nat 0) Inf = Nat 0
nExp (Nat 1) Inf = Nat 1
nExp (Nat _) Inf = Inf
nExp (Nat x) (Nat y) = Nat (x ^ y)
nMin :: Nat' -> Nat' -> Nat'
nMin Inf x = x
nMin x Inf = x
nMin (Nat x) (Nat y) = Nat (min x y)
nMax :: Nat' -> Nat' -> Nat'
nMax Inf _ = Inf
nMax _ Inf = Inf
nMax (Nat x) (Nat y) = Nat (max x y)
{- | @nSub x y = Just z@ iff @z@ is the unique value
such that @Add y z = Just x@. -}
nSub :: Nat' -> Nat' -> Maybe Nat'
nSub Inf (Nat _) = Just Inf
nSub (Nat x) (Nat y)
| x >= y = Just (Nat (x - y))
nSub _ _ = Nothing
-- XXX:
-- Does it make sense to define:
-- nDiv Inf (Nat x) = Inf
-- nMod Inf (Nat x) = Nat 0
{- | Rounds down.
> y * q + r = x
> x / y = q with remainder r
> 0 <= r && r < y
We don't allow `Inf` in the first argument for two reasons:
1. It matches the behavior of `nMod`,
2. The well-formedness constraints can be expressed as a conjunction.
-}
nDiv :: Nat' -> Nat' -> Maybe Nat'
nDiv _ (Nat 0) = Nothing
nDiv Inf _ = Nothing
nDiv (Nat x) (Nat y) = Just (Nat (div x y))
nDiv (Nat _) Inf = Just (Nat 0)
nMod :: Nat' -> Nat' -> Maybe Nat'
nMod _ (Nat 0) = Nothing
nMod Inf _ = Nothing
nMod (Nat x) (Nat y) = Just (Nat (mod x y))
nMod (Nat x) Inf = Just (Nat x) -- inf * 0 + x = 0 + x
-- | Rounds up.
-- @lg2 x = y@, iff @y@ is the smallest number such that @x <= 2 ^ y@
nLg2 :: Nat' -> Nat'
nLg2 Inf = Inf
nLg2 (Nat 0) = Nat 0
nLg2 (Nat n) = case genLog n 2 of
Just (x,exact) | exact -> Nat x
| otherwise -> Nat (x + 1)
Nothing -> panic "Cryptol.TypeCheck.Solver.InfNat.nLg2"
[ "genLog returned Nothing" ]
-- | @nWidth n@ is number of bits needed to represent all numbers
-- from 0 to n, inclusive. @nWidth x = nLg2 (x + 1)@.
nWidth :: Nat' -> Nat'
nWidth Inf = Inf
nWidth (Nat n) = Nat (widthInteger n)
{- | @length ([ x, y .. ] : [_][w])@
We don't check that the second element fits in `w` many bits as the
second element may not be part of the list.
For example, the length of @[ 0 .. ] : [_][0]@ is @nLenFromThen 0 1 0@,
which should evaluate to 1. -}
{- XXX: It would appear that the actual notation also requires `y` to fit in...
It is not clear if that's a good idea. Consider, for example,
[ 1, 4 .., 2 ]
Cryptol infers that this list has one element, but it insists that the
width of the elements be at least 3, to accommodate the 4.
-}
nLenFromThen :: Nat' -> Nat' -> Nat' -> Maybe Nat'
nLenFromThen a@(Nat x) b@(Nat y) wi@(Nat w)
| wi < nWidth a = Nothing
| y > x = nLenFromThenTo a b (Nat (2^w - 1))
| y < x = nLenFromThenTo a b (Nat 0)
nLenFromThen _ _ _ = Nothing
-- | @length [ x, y .. z ]@
nLenFromThenTo :: Nat' -> Nat' -> Nat' -> Maybe Nat'
nLenFromThenTo (Nat x) (Nat y) (Nat z)
| step /= 0 = let len = div dist step + 1
in Just $ Nat $ if x > y
-- decreasing
then (if z > x then 0 else len)
-- increasing
else (if z < x then 0 else len)
where
step = abs (x - y)
dist = abs (x - z)
nLenFromThenTo _ _ _ = Nothing
{- Note [Sequences of Length 0]
nLenFromThenTo x y z == 0
case 1: x > y && z > x
case 2: x <= y && z < x
nLenFromThen x y w == 0
impossible
-}
{- Note [Sequences of Length 1]
`nLenFromThenTo x y z == 1`
dist < step && (x > y && z <= x || y >= x && z >= x)
case 1: dist < step && x > y && z <= x
case 2: dist < step && y >= x && z >= x
case 1: if `z <= x`,
then `x - z >= 0`,
hence `dist = x - z` (a)
if `x > y`
then `x - y` > 0
hence `step = x - y` (b)
from (a) and (b):
`dist < step`
`x - z < x - y`
`-z < -y`
`z > y`
case 1 summary: x >= z && z > y
case 2: if y >= x, then step = y - x (a)
if z >= x, then dist = z - x (b)
dist < step =
(z - x) < (y - x) =
(z < y)
case 2 summary: y > z, z >= x
------------------------
`nLenFromThen x y w == 1`
| y > x = nLenFromThenTo x y (Nat (2^w - 1))
| y < x = nLenFromThenTo x y (Nat 0)
y >= 2^w, y > x
-}
--------------------------------------------------------------------------------
-- | Compute the logarithm of a number in the given base, rounded down to the
-- closest integer. The boolean indicates if we the result is exact
-- (i.e., True means no rounding happened, False means we rounded down).
-- The logarithm base is the second argument.
genLog :: Integer -> Integer -> Maybe (Integer, Bool)
genLog x 0 = if x == 1 then Just (0, True) else Nothing
genLog _ 1 = Nothing
genLog 0 _ = Nothing
genLog x base = Just (exactLoop 0 x)
where
exactLoop s i
| i == 1 = (s,True)
| i < base = (s,False)
| otherwise =
let s1 = s + 1
in s1 `seq` case divMod i base of
(j,r)
| r == 0 -> exactLoop s1 j
| otherwise -> (underLoop s1 j, False)
underLoop s i
| i < base = s
| otherwise = let s1 = s + 1 in s1 `seq` underLoop s1 (div i base)
-- | Compute the number of bits required to represent the given integer.
widthInteger :: Integer -> Integer
widthInteger x = go' 0 (if x < 0 then complement x else x)
where
go s 0 = s
go s n = let s' = s + 1 in s' `seq` go s' (n `shiftR` 1)
go' s n
| n < bit 32 = go s n
| otherwise = let s' = s + 32 in s' `seq` go' s' (n `shiftR` 32)
-- | Compute the exact root of a natural number.
-- The second argument specifies which root we are computing.
rootExact :: Integer -> Integer -> Maybe Integer
rootExact x y = do (z,True) <- genRoot x y
return z
{- | Compute the the n-th root of a natural number, rounded down to
the closest natural number. The boolean indicates if the result
is exact (i.e., True means no rounding was done, False means rounded down).
The second argument specifies which root we are computing. -}
genRoot :: Integer -> Integer -> Maybe (Integer, Bool)
genRoot _ 0 = Nothing
genRoot x0 1 = Just (x0, True)
genRoot x0 root = Just (search 0 (x0+1))
where
search from to = let x = from + div (to - from) 2
a = x ^ root
in case compare a x0 of
EQ -> (x, True)
LT | x /= from -> search x to
| otherwise -> (from, False)
GT | x /= to -> search from x
| otherwise -> (from, False)
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Selector.hs 0000644 0000000 0000000 00000010552 12737220176 021101 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE PatternGuards, Safe #-}
module Cryptol.TypeCheck.Solver.Selector (tryHasGoal) where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.InferTypes
import Cryptol.TypeCheck.Monad( InferM, unify, newGoals, lookupNewtype
, newType, applySubst, addHasGoal, solveHasGoal
)
import Cryptol.TypeCheck.Subst(listSubst,apSubst)
import Cryptol.Utils.Ident (Ident)
import Cryptol.Utils.PP(text,pp,ordinal,(<+>))
import Cryptol.Utils.Panic(panic)
import Control.Monad(forM,guard)
recordType :: [Ident] -> InferM Type
recordType labels =
do fields <- forM labels $ \l ->
do t <- newType (text "record field" <+> pp l) KType
return (l,t)
return (TRec fields)
tupleType :: Int -> InferM Type
tupleType n =
do fields <- mapM (\x -> newType (ordinal x <+> text "tuple field") KType)
[ 0 .. (n-1) ]
return (tTuple fields)
listType :: Int -> InferM Type
listType n =
do elems <- newType (text "sequence element type") KType
return (tSeq (tNum n) elems)
improveSelector :: Selector -> Type -> InferM (Expr -> Expr)
improveSelector sel outerT =
case sel of
RecordSel _ mb -> cvt recordType mb
TupleSel _ mb -> cvt tupleType mb
ListSel _ mb -> cvt listType mb
where
cvt _ Nothing = return id
cvt f (Just a) = do ty <- f a
cs <- unify ty outerT
case cs of
[] -> return id
_ -> do newGoals CtExactType cs
return (`ECast` ty)
{- | Compute the type of a field based on the selector.
The given type should be "zonked" (i.e., substitution was applied to it),
and (outermost) type synonyms have been expanded.
-}
solveSelector :: Selector -> Type -> InferM (Maybe Type)
solveSelector sel outerT =
case (sel, outerT) of
(RecordSel l _, ty) ->
case ty of
TRec fs -> return (lookup l fs)
TCon (TC TCSeq) [len,el] -> liftSeq len el
TCon (TC TCFun) [t1,t2] -> liftFun t1 t2
TCon (TC (TCNewtype (UserTC x _))) ts ->
do mb <- lookupNewtype x
case mb of
Nothing -> return Nothing
Just nt ->
case lookup l (ntFields nt) of
Nothing -> return Nothing
Just t ->
do let su = listSubst (zip (map tpVar (ntParams nt)) ts)
newGoals (CtPartialTypeFun $ UserTyFun x)
$ apSubst su $ ntConstraints nt
return $ Just $ apSubst su t
_ -> return Nothing
(TupleSel n _, ty) ->
case ty of
TCon (TC (TCTuple m)) ts ->
return $ do guard (0 <= n && n < m)
return $ ts !! n
TCon (TC TCSeq) [len,el] -> liftSeq len el
TCon (TC TCFun) [t1,t2] -> liftFun t1 t2
_ -> return Nothing
(ListSel n _, TCon (TC TCSeq) [l,t]) ->
do newGoals CtSelector [ (l .+. tNum (1::Int)) >== tNum n ]
return (Just t)
_ -> return Nothing
where
liftSeq len el =
do mb <- solveSelector sel (tNoUser el)
return $ do el' <- mb
return (TCon (TC TCSeq) [len,el'])
liftFun t1 t2 =
do mb <- solveSelector sel (tNoUser t2)
return $ do t2' <- mb
return (TCon (TC TCFun) [t1,t2'])
-- | Solve has-constraints.
tryHasGoal :: HasGoal -> InferM ()
tryHasGoal has
| TCon (PC (PHas sel)) [ th, ft ] <- goal (hasGoal has) =
do outerCast <- improveSelector sel th
outerT <- tNoUser `fmap` applySubst th
mbInnerT <- solveSelector sel outerT
case mbInnerT of
Nothing -> addHasGoal has
Just innerT ->
do cs <- unify innerT ft
innerCast <- case cs of
[] -> return id
_ -> do newGoals CtExactType cs
return (`ECast` ft)
solveHasGoal (hasName has) (innerCast . (`ESel` sel) . outerCast)
| otherwise = panic "hasGoalSolved"
[ "Unexpected selector proposition:"
, show (hasGoal has)
]
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Simplify.hs 0000644 0000000 0000000 00000012362 12737220176 021116 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiWayIf #-}
module Cryptol.TypeCheck.Solver.Simplify (
tryRewritePropAsSubst
) where
import Cryptol.Prims.Syntax (TFun(..))
import Cryptol.TypeCheck.AST (Type(..),Prop,TVar,pIsEq,isFreeTV,TCon(..))
import Cryptol.TypeCheck.Solver.Numeric.Interval (Interval,iIsFin,typeInterval)
import Cryptol.TypeCheck.Subst (fvs)
import Control.Monad (msum,guard,mzero)
import Data.Function (on)
import Data.List (sortBy)
import Data.Maybe (catMaybes,listToMaybe)
import Data.Map (Map)
import qualified Data.Set as Set
-- | When given an equality constraint, attempt to rewrite it to the form `?x =
-- ...`, by moving all occurrences of `?x` to the LHS, and any other variables
-- to the RHS. This will only work when there's only one unification variable
-- present in the prop.
tryRewritePropAsSubst :: Map TVar Interval -> Prop -> Maybe (TVar,Type)
tryRewritePropAsSubst fins p =
do (x,y) <- pIsEq p
let vars = Set.toList (Set.filter isFreeTV (fvs p))
listToMaybe $ sortBy (flip compare `on` rank)
$ catMaybes [ tryRewriteEq fins var x y | var <- vars ]
-- | Rank a rewrite, favoring expressions that have fewer subtractions than
-- additions.
rank :: (TVar,Type) -> Int
rank (_,ty) = go ty
where
go (TCon (TF TCAdd) ts) = sum (map go ts) + 1
go (TCon (TF TCSub) ts) = sum (map go ts) - 1
go (TCon (TF TCMul) ts) = sum (map go ts) + 1
go (TCon (TF TCDiv) ts) = sum (map go ts) - 1
go (TCon _ ts) = sum (map go ts)
go _ = 0
-- | Rewrite an equation with respect to a unification variable ?x, into the
-- form `?x = t`. There are two interesting cases to consider (four with
-- symmetry):
--
-- * ?x = ty
-- * expr containing ?x = expr
--
-- In the first case, we just return the type variable and the type, but in the
-- second we try to rewrite the equation until it's in the form of the first
-- case.
tryRewriteEq :: Map TVar Interval -> TVar -> Type -> Type -> Maybe (TVar,Type)
tryRewriteEq fins uvar l r =
msum [ do guard (uvarTy == l && uvar `Set.notMember` rfvs)
return (uvar, r)
, do guard (uvarTy == r && uvar `Set.notMember` lfvs)
return (uvar, l)
, do guard (uvar `Set.notMember` rfvs)
ty <- rewriteLHS fins uvar l r
return (uvar,ty)
, do guard (uvar `Set.notMember` lfvs)
ty <- rewriteLHS fins uvar r l
return (uvar,ty)
]
where
uvarTy = TVar uvar
lfvs = fvs l
rfvs = fvs r
-- | Check that a type contains only finite type variables.
allFin :: Map TVar Interval -> Type -> Bool
allFin ints ty = iIsFin (typeInterval ints ty)
-- | Rewrite an equality until the LHS is just `uvar`. Return the rewritten RHS.
--
-- There are a few interesting cases when rewriting the equality:
--
-- A o B = R when `uvar` is only present in A
-- A o B = R when `uvar` is only present in B
--
-- In the first case, as we only consider addition and subtraction, the
-- rewriting will continue on the left, after moving the `B` side to the RHS of
-- the equation. In the second case, if the operation is addition, the `A` side
-- will be moved to the RHS, with rewriting continuing in `B`. However, in the
-- case of subtraction, the `B` side is moved to the RHS, and rewriting
-- continues on the RHS instead.
--
-- In both cases, if the operation is addition, rewriting will only continue if
-- the operand being moved to the RHS is known to be finite. If this check was
-- not done, we would end up violating the well-definedness condition for
-- subtraction (for a, b: well defined (a - b) iff fin b).
rewriteLHS :: Map TVar Interval -> TVar -> Type -> Type -> Maybe Type
rewriteLHS fins uvar = go
where
go (TVar tv) rhs | tv == uvar = return rhs
go (TCon (TF tf) [x,y]) rhs =
do let xfvs = fvs x
yfvs = fvs y
inX = Set.member uvar xfvs
inY = Set.member uvar yfvs
if | inX && inY -> mzero
| inX -> balanceR x tf y rhs
| inY -> balanceL x tf y rhs
| otherwise -> mzero
-- discard type synonyms, the rewriting will make them no longer apply
go (TUser _ _ l) rhs =
go l rhs
-- records won't work here.
go _ _ =
mzero
-- invert the type function to balance the equation, when the variable occurs
-- on the LHS of the expression `x tf y`
balanceR x TCAdd y rhs = do guardFin y
go x (TCon (TF TCSub) [rhs,y])
balanceR x TCSub y rhs = go x (TCon (TF TCAdd) [rhs,y])
balanceR _ _ _ _ = mzero
-- invert the type function to balance the equation, when the variable occurs
-- on the RHS of the expression `x tf y`
balanceL x TCAdd y rhs = do guardFin y
go y (TCon (TF TCSub) [rhs,x])
balanceL x TCSub y rhs = go (TCon (TF TCAdd) [rhs,y]) x
balanceL _ _ _ _ = mzero
-- guard that the type is finite
--
-- XXX this ignores things like `min x inf` where x is finite, and just
-- assumes that it won't work.
guardFin ty = guard (allFin fins ty)
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Utils.hs 0000644 0000000 0000000 00000004533 12737220176 020423 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.TypeCheck.Solver.Utils where
import Cryptol.TypeCheck.AST
import Control.Monad(mplus,guard)
import Data.Maybe(listToMaybe)
-- | All ways to split a type in the form: `a + t1`, where `a` is a variable.
splitVarSummands :: Type -> [(TVar,Type)]
splitVarSummands ty0 = [ (x,t1) | (x,t1) <- go ty0, tNum (0::Int) /= t1 ]
where
go ty = case ty of
TVar x -> return (x, tNum (0::Int))
TRec {} -> []
TUser _ _ t -> go t
TCon (TF TCAdd) [t1,t2] ->
do (a,yes) <- go t1
return (a, yes .+. t2)
`mplus`
do (a,yes) <- go t2
return (a, t1 .+. yes)
TCon _ _ -> [] -- XXX: we could do some distributivity etc
-- | Check if we can express a type in the form: `a + t1`.
splitVarSummand :: TVar -> Type -> Maybe Type
splitVarSummand a ty = listToMaybe [ t | (x,t) <- splitVarSummands ty, x == a ]
{- | Check if we can express a type in the form: `k + t1`,
where `k` is a constant > 0.
This assumes that the type has been simplified already,
so that constants are floated to the left. -}
splitConstSummand :: Type -> Maybe (Integer, Type)
splitConstSummand ty =
case ty of
TVar {} -> Nothing
TRec {} -> Nothing
TUser _ _ t -> splitConstSummand t
TCon (TF TCAdd) [t1,t2] ->
do (k,t1') <- splitConstSummand t1
case t1' of
TCon (TC (TCNum 0)) [] -> return (k, t2)
_ -> return (k, t1' .+. t2)
TCon (TC (TCNum k)) [] -> guard (k > 0) >> return (k, tNum (0::Int))
TCon {} -> Nothing
{- | Check if we can express a type in the form: `k * t1`,
where `k` is a constant > 1
This assumes that the type has been simplified already,
so that constants are floated to the left. -}
splitConstFactor :: Type -> Maybe (Integer, Type)
splitConstFactor ty =
case ty of
TVar {} -> Nothing
TRec {} -> Nothing
TUser _ _ t -> splitConstFactor t
TCon (TF TCMul) [t1,t2] ->
do (k,t1') <- splitConstFactor t1
return (k, t1' .*. t2)
TCon (TC (TCNum k)) [] -> guard (k > 1) >> return (k, tNum (1::Int))
TCon {} -> Nothing
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/ 0000755 0000000 0000000 00000000000 12737220176 020364 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/AST.hs 0000644 0000000 0000000 00000027274 12737220176 021363 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- The sytnax of numeric propositions.
{-# LANGUAGE Safe #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.TypeCheck.Solver.Numeric.AST
( Name(..), ppName
, Prop(..), cryPropExprs, cryPropFVS
, ppProp, ppPropPrec
, Expr(..), zero, one, two, inf, cryAnds, cryOrs
, cryExprExprs, cryRebuildExpr
, cryExprFVS
, ppExpr, ppExprPrec
, Nat'(..)
, IfExpr, IfExpr'(..), ppIf, ppIfExpr
, Subst, HasVars(..), cryLet, composeSubst, doAppSubst
) where
import Cryptol.TypeCheck.AST(TVar)
import Cryptol.TypeCheck.PP(pp)
import Cryptol.TypeCheck.Solver.InfNat ( Nat'(..) )
import Cryptol.Utils.PP ( Doc, text, (<+>), hang, ($$), char, (<>)
, parens, integer, sep )
import Cryptol.Utils.Panic ( panic )
import Cryptol.Utils.Misc ( anyJust )
-- import Data.GenericTrie (TrieKey)
import GHC.Generics(Generic)
import Data.Maybe (fromMaybe)
import Data.Map ( Map )
import qualified Data.Map as Map
import Data.Set ( Set )
import qualified Data.Set as Set
import qualified Control.Applicative as A
import Control.Monad ( liftM, ap )
infixr 2 :||
infixr 3 :&&
infix 4 :==, :>, :>=, :==:, :>:
infixl 6 :+, :-
infixl 7 :*
infixr 8 :^^
data Name = UserName TVar | SysName Int
deriving (Show,Eq,Ord,Generic)
-- | Propopsitions, representing Cryptol's numeric constraints (and a bit more).
data Prop =
-- Preidcates on natural numbers with infinity.
-- After simplification, the only one of these should be `fin x`,
-- where `x` is a variable.
Fin Expr | Expr :== Expr | Expr :>= Expr | Expr :> Expr
-- Predicate on strict natural numbers (i.e., no infinities)
-- Should be introduced by 'cryNatOp', to eliminte 'inf'.
| Expr :==: Expr | Expr :>: Expr
-- Standard logical strucutre>
| Prop :&& Prop | Prop :|| Prop
| Not Prop
| PFalse | PTrue
deriving (Eq,Show,Generic)
-- | Expressions, representing Cryptol's numeric types.
data Expr = K Nat'
| Var Name
| Expr :+ Expr -- total
| Expr :- Expr -- partial: x >= y, fin y
| Expr :* Expr -- total
| Div Expr Expr -- partial: fin x, y >= 1
| Mod Expr Expr -- partial: fin x, y >= 1
| Expr :^^ Expr -- total
| Min Expr Expr -- total
| Max Expr Expr -- total
| Width Expr -- total
| LenFromThen Expr Expr Expr -- partial: x /= y, w >= width x
| LenFromThenTo Expr Expr Expr -- partial: x /= y
deriving (Eq,Show,Generic,Ord)
-- | The constant @0@.
zero :: Expr
zero = K (Nat 0)
-- | The constant @1@.
one :: Expr
one = K (Nat 1)
-- | The constant @2@.
two :: Expr
two = K (Nat 2)
-- | The constant @infinity@.
inf :: Expr
inf = K Inf
-- | Make a conjucntion of the given properties.
cryAnds :: [Prop] -> Prop
cryAnds [] = PTrue
cryAnds ps = foldr1 (:&&) ps
-- | Make a disjunction of the given properties.
cryOrs :: [Prop] -> Prop
cryOrs [] = PFalse
cryOrs ps = foldr1 (:||) ps
-- | Compute all expressions in a property.
cryPropExprs :: Prop -> [Expr]
cryPropExprs = go []
where
go es prop =
case prop of
PTrue -> es
PFalse -> es
Not p -> go es p
p :&& q -> go (go es q) p
p :|| q -> go (go es q) p
Fin x -> x : es
x :== y -> x : y : es
x :> y -> x : y : es
x :>= y -> x : y : es
x :==: y -> x : y : es
x :>: y -> x : y : es
-- | Compute the immediate sub-expressions of an expression.
cryExprExprs :: Expr -> [Expr]
cryExprExprs expr =
case expr of
K _ -> []
Var _ -> []
x :+ y -> [x,y]
x :- y -> [x,y]
x :* y -> [x,y]
Div x y -> [x,y]
Mod x y -> [x,y]
x :^^ y -> [x,y]
Min x y -> [x,y]
Max x y -> [x,y]
Width x -> [x]
LenFromThen x y z -> [x,y,z]
LenFromThenTo x y z -> [x,y,z]
-- | Rebuild an expression, using the top-level strucutre of the first
-- expression, but the second list of expressions as sub-expressions.
cryRebuildExpr :: Expr -> [Expr] -> Expr
cryRebuildExpr expr args =
case (expr,args) of
(K _, []) -> expr
(Var _, []) -> expr
(_ :+ _k, [x,y]) -> x :+ y
(_ :- _ , [x,y]) -> x :- y
(_ :* _ , [x,y]) -> x :* y
(Div _ _, [x,y]) -> Div x y
(Mod _ _, [x,y]) -> Mod x y
(_ :^^ _, [x,y]) -> x :^^ y
(Min _ _, [x,y]) -> Min x y
(Max _ _, [x,y]) -> Max x y
(Width _, [x]) -> Width x
(LenFromThen _ _ _ , [x,y,z]) -> LenFromThen x y z
(LenFromThenTo _ _ _ , [x,y,z]) -> LenFromThenTo x y z
_ -> panic "cryRebuildExpr" $ map show
$ text "expr:" <+> ppExpr expr
: [ text "arg:" <+> ppExpr a | a <- args ]
-- | Compute the free variables in an expression.
cryExprFVS :: Expr -> Set Name
cryExprFVS expr =
case expr of
Var x -> Set.singleton x
_ -> Set.unions (map cryExprFVS (cryExprExprs expr))
-- | Compute the free variables in a proposition.
cryPropFVS :: Prop -> Set Name
cryPropFVS = Set.unions . map cryExprFVS . cryPropExprs
data IfExpr' p a = If p (IfExpr' p a) (IfExpr' p a) | Return a | Impossible
deriving Eq
type IfExpr = IfExpr' Prop
instance Monad (IfExpr' p) where
return = Return
fail _ = Impossible
m >>= k = case m of
Impossible -> Impossible
Return a -> k a
If p t e -> If p (t >>= k) (e >>= k)
instance Functor (IfExpr' p) where
fmap = liftM
instance A.Applicative (IfExpr' p) where
pure = return
(<*>) = ap
--------------------------------------------------------------------------------
-- Substitution
--------------------------------------------------------------------------------
type Subst = Map Name Expr
composeSubst :: Subst -> Subst -> Subst
composeSubst g f = Map.union f' g
where
f' = fmap (\e -> fromMaybe e (apSubst g e)) f
cryLet :: HasVars e => Name -> Expr -> e -> Maybe e
cryLet x e = apSubst (Map.singleton x e)
doAppSubst :: HasVars a => Subst -> a -> a
doAppSubst su a = fromMaybe a (apSubst su a)
-- | Replaces occurances of the name with the expression.
-- Returns 'Nothing' if there were no occurances of the name.
class HasVars ast where
apSubst :: Subst -> ast -> Maybe ast
-- | This is used in the simplification to "apply" substitutions to Props.
instance HasVars Bool where
apSubst _ _ = Nothing
instance HasVars Expr where
apSubst su = go
where
go expr =
case expr of
K _ -> Nothing
Var b -> Map.lookup b su
x :+ y -> bin (:+) x y
x :- y -> bin (:-) x y
x :* y -> bin (:*) x y
x :^^ y -> bin (:^^) x y
Div x y -> bin Div x y
Mod x y -> bin Mod x y
Min x y -> bin Min x y
Max x y -> bin Max x y
Width x -> Width `fmap` go x
LenFromThen x y w -> three LenFromThen x y w
LenFromThenTo x y z -> three LenFromThen x y z
bin f x y = do [x',y'] <- anyJust go [x,y]
return (f x' y')
three f x y z = do [x',y',z'] <- anyJust go [x,y,z]
return (f x' y' z')
instance HasVars Prop where
apSubst su = go
where
go prop =
case prop of
PFalse -> Nothing
PTrue -> Nothing
Not p -> Not `fmap` go p
p :&& q -> bin (:&&) p q
p :|| q -> bin (:||) p q
Fin x -> Fin `fmap` apSubst su x
x :== y -> twoE (:==) x y
x :>= y -> twoE (:>=) x y
x :> y -> twoE (:>) x y
x :==: y -> twoE (:==:) x y
x :>: y -> twoE (:>) x y
bin f x y = do [x',y'] <- anyJust go [x,y]
return (f x' y')
twoE f x y = do [x',y'] <- anyJust (apSubst su) [x,y]
return (f x' y')
--------------------------------------------------------------------------------
-- Tries
--------------------------------------------------------------------------------
-- instance TrieKey Name
-- instance TrieKey Prop
-- instance TrieKey Expr
--------------------------------------------------------------------------------
-- Pretty Printing
--------------------------------------------------------------------------------
-- | Pretty print a name.
ppName :: Name -> Doc
ppName name =
case name of
UserName x -> pp x
SysName x -> char '_' <> text (names !! x)
-- | An infinite list of names, for pretty prinitng.
names :: [String]
names = concatMap gen [ 0 :: Integer .. ]
where
gen x = [ a : suff x | a <- [ 'a' .. 'z' ] ]
suff 0 = ""
suff x = show x
-- | Pretty print a top-level property.
ppProp :: Prop -> Doc
ppProp = ppPropPrec 0
-- | Pretty print a proposition, in the given precedence context.
ppPropPrec :: Int -> Prop -> Doc
ppPropPrec prec prop =
case prop of
Fin x -> fun "fin" ppExprPrec x
x :== y -> bin "==" 4 1 1 ppExprPrec x y
x :>= y -> bin ">=" 4 1 1 ppExprPrec x y
x :> y -> bin ">" 4 1 1 ppExprPrec x y
x :==: y -> bin "==#" 4 1 1 ppExprPrec x y
x :>: y -> bin ">#" 4 1 1 ppExprPrec x y
p :&& q -> bin "&&" 3 1 0 ppPropPrec p q
p :|| q -> bin "||" 2 1 0 ppPropPrec p q
Not p -> fun "not" ppPropPrec p
PTrue -> text "True"
PFalse -> text "False"
where
wrap p d = if prec > p then parens d else d
fun f how x = wrap 10 (text f <+> how 11 x)
bin op opP lMod rMod how x y =
wrap opP (sep [ how (opP + lMod) x, text op, how (opP + rMod) y ])
-- | Pretty print an expression at the top level.
ppExpr :: Expr -> Doc
ppExpr = ppExprPrec 0
-- | Pretty print an expression, in the given precedence context.
ppExprPrec :: Int -> Expr -> Doc
ppExprPrec prec expr =
case expr of
K Inf -> text "inf"
K (Nat n) -> integer n
Var a -> ppName a
x :+ y -> bin "+" 6 0 1 x y
x :- y -> bin "-" 6 0 1 x y
x :* y -> bin "*" 7 0 1 x y
Div x y -> fun "div" [x,y]
Mod x y -> fun "mod" [x,y]
x :^^ y -> bin "^^" 8 1 0 x y
Min x y -> fun "min" [x,y]
Max x y -> fun "max" [x,y]
Width x -> fun "width" [x]
LenFromThen x y w -> fun "lenFromThen" [x,y,w]
LenFromThenTo x y z -> fun "lenFromThenTo" [x,y,z]
where
wrap p d = if prec > p then parens d else d
fun f xs = wrap 10 (text f <+> sep (map (ppExprPrec 11) xs))
bin op opP lMod rMod x y =
wrap opP
(ppExprPrec (opP + lMod) x <+> text op <+> ppExprPrec (opP + rMod) y)
-- | Pretty print an experssion with ifs.
ppIfExpr :: IfExpr Expr -> Doc
ppIfExpr = ppIf ppProp ppExpr
-- | Pretty print an experssion with ifs.
ppIf :: (p -> Doc) -> (a -> Doc) -> IfExpr' p a -> Doc
ppIf ppAtom ppVal = go
where
go expr =
case expr of
If p t e -> hang (text "if" <+> ppAtom p) 2
( (text "then" <+> go t) $$
(text "else" <+> go e)
)
Return e -> ppVal e
Impossible -> text ""
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/Defined.hs 0000644 0000000 0000000 00000004103 12737220176 022254 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Solver.Numeric.Defined where
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.Utils.Panic ( panic )
-- | A condition ensure that the given *basic* proposition makes sense.
cryDefinedProp :: Prop -> Prop
cryDefinedProp prop =
case prop of
Fin x -> cryDefined x
x :== y -> cryDefined x :&& cryDefined y
x :>= y -> cryDefined x :&& cryDefined y
Not p -> cryDefinedProp p
_ -> panic "cryDefinedProp" [ "Not a simple property:"
, show (ppProp prop)
]
-- | Generate a property ensuring that the expression is well-defined.
-- This might be a bit too strict. For example, we reject things like
-- @max inf (0 - 1)@, which one might think would simplify to @inf@.
cryDefined :: Expr -> Prop
cryDefined expr =
case expr of
K _ -> PTrue
Var _ -> PTrue -- Variables are always assumed to be OK.
-- The idea is that we are going to check for
-- defined-ness before instantiating variables.
x :+ y -> cryDefined x :&& cryDefined y
x :- y -> cryDefined x :&& cryDefined y :&&
Fin y :&& x :>= y
x :* y -> cryDefined x :&& cryDefined y
Div x y -> cryDefined x :&& cryDefined y :&&
Fin x :&& y :>= K (Nat 1)
Mod x y -> cryDefined x :&& cryDefined y :&&
Fin x :&& y :>= K (Nat 1)
x :^^ y -> cryDefined x :&& cryDefined y
Min x y -> cryDefined x :&& cryDefined y
Max x y -> cryDefined x :&& cryDefined y
Width x -> cryDefined x
LenFromThen x y w ->
cryDefined x :&& cryDefined y :&& cryDefined w :&&
Fin x :&& Fin y :&& Fin w :&& Not (x :== y) :&& w :>= Width x
LenFromThenTo x y z ->
cryDefined x :&& cryDefined y :&& cryDefined z :&&
Fin x :&& Fin y :&& Fin z :&& Not (x :== y)
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/Fin.hs 0000644 0000000 0000000 00000005133 12737220176 021436 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Simplification of `fin` constraints.
{-# LANGUAGE PatternGuards #-}
module Cryptol.TypeCheck.Solver.Numeric.Fin where
import Data.Map (Map)
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.InferTypes
import Cryptol.TypeCheck.Solver.Numeric.Interval
import Cryptol.TypeCheck.Solver.InfNat
cryIsFin :: Map TVar Interval -> Goal -> Solved
cryIsFin varInfo g =
case pIsFin (goal g) of
Just ty -> cryIsFinType varInfo g ty
Nothing -> Unsolved
cryIsFinType :: Map TVar Interval -> Goal -> Type -> Solved
cryIsFinType varInfo g ty =
case tNoUser ty of
TCon (TC tc) [] | TCNum _ <- tc -> solved []
TCon (TF f) ts ->
case (f,ts) of
(TCAdd,[t1,t2]) -> solved [ pFin t1, pFin t2 ]
(TCSub,[t1,_ ]) -> solved [ pFin t1 ]
-- fin (x * y)
(TCMul,[t1,t2])
| iLower i1 >= Nat 1 && iIsFin i1 -> solved [ pFin t2 ]
| iLower i2 >= Nat 1 && iIsFin i2 -> solved [ pFin t1 ]
| iLower i1 >= Nat 1 &&
iLower i2 >= Nat 1 -> solved [ pFin t1, pFin t2 ]
| iIsFin i1 && iIsFin i2 -> solved []
where
i1 = typeInterval varInfo t1
i2 = typeInterval varInfo t2
(TCDiv, [t1,_]) -> solved [ pFin t1 ]
(TCMod, [_,_]) -> solved []
-- fin (x ^ y)
(TCExp, [t1,t2])
| iLower i1 == Inf -> solved [ t2 =#= tZero ]
| iLower i2 == Inf -> solved [ tOne >== t1 ]
| iLower i1 >= Nat 2 -> solved [ pFin t1, pFin t2 ]
| iLower i2 >= Nat 1 -> solved [ pFin t1, pFin t2 ]
| Just x <- iUpper i1, x <= Nat 1 -> solved []
| Just (Nat 0) <- iUpper i2 -> solved []
where
i1 = typeInterval varInfo t1
i2 = typeInterval varInfo t2
-- fin (min x y)
(TCMin, [t1,t2])
| iIsFin i1 -> solved []
| iIsFin i2 -> solved []
| Just x <- iUpper i1, x <= iLower i2 -> solved [ pFin t1 ]
| Just x <- iUpper i2, x <= iLower i1 -> solved [ pFin t2 ]
where
i1 = typeInterval varInfo t1
i2 = typeInterval varInfo t2
(TCMax, [t1,t2]) -> solved [ pFin t1, pFin t2 ]
(TCWidth, [t1]) -> solved [ pFin t1 ]
(TCLenFromThen,[_,_,_]) -> solved []
(TCLenFromThenTo,[_,_,_]) -> solved []
_ -> Unsolved
_ -> Unsolved
where
solved ps = Solved Nothing [ g { goal = p } | p <- ps ]
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/ImportExport.hs 0000644 0000000 0000000 00000011675 12737220176 023406 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Solver.Numeric.ImportExport
( ExportM
, exportProp
, exportType
, runExportM
, exportPropM
, exportTypeM
, importProp
, importType
) where
import Cryptol.TypeCheck.Solver.Numeric.AST
import qualified Cryptol.TypeCheck.AST as Cry
import MonadLib
exportProp :: Cry.Prop -> Maybe Prop
exportProp = runExportM . exportPropM
exportType :: Cry.Prop -> Maybe Expr
exportType = runExportM . exportTypeM
runExportM :: ExportM a -> Maybe a
runExportM = either (\_ -> Nothing) Just
. runId
. runExceptionT
type ExportM = ExceptionT () Id
exportPropM :: Cry.Prop -> ExportM Prop
exportPropM ty =
case ty of
Cry.TUser _ _ t -> exportPropM t
Cry.TRec {} -> raise ()
Cry.TVar {} -> raise ()
Cry.TCon (Cry.PC pc) ts ->
mapM exportTypeM ts >>= \ets ->
case (pc, ets) of
(Cry.PFin, [t]) -> return (Fin t)
(Cry.PEqual, [t1,t2]) -> return (t1 :== t2)
(Cry.PNeq, [t1,t2]) -> return (Not (t1 :== t2))
(Cry.PGeq, [t1,t2]) -> return (t1 :>= t2)
_ -> raise ()
Cry.TCon _ _ -> raise ()
exportTypeM :: Cry.Type -> ExportM Expr
exportTypeM ty =
case ty of
Cry.TUser _ _ t -> exportTypeM t
Cry.TRec {} -> raise ()
Cry.TVar x -> return $ Var $ UserName x
Cry.TCon tc ts ->
case tc of
Cry.TC Cry.TCInf -> return (K Inf)
Cry.TC (Cry.TCNum x) -> return (K (Nat x))
Cry.TC _ -> raise ()
Cry.TF f ->
mapM exportTypeM ts >>= \ets ->
case (f, ets) of
(Cry.TCAdd, [t1,t2]) -> return (t1 :+ t2)
(Cry.TCSub, [t1,t2]) -> return (t1 :- t2)
(Cry.TCMul, [t1,t2]) -> return (t1 :* t2)
(Cry.TCDiv, [t1,t2]) -> return (Div t1 t2)
(Cry.TCMod, [t1,t2]) -> return (Mod t1 t2)
(Cry.TCExp, [t1,t2]) -> return (t1 :^^ t2)
(Cry.TCMin, [t1,t2]) -> return (Min t1 t2)
(Cry.TCMax, [t1,t2]) -> return (Max t1 t2)
(Cry.TCWidth, [t1]) -> return (Width t1)
(Cry.TCLenFromThen, [t1,t2,t3]) -> return (LenFromThen t1 t2 t3)
(Cry.TCLenFromThenTo, [t1,t2,t3]) -> return (LenFromThenTo t1 t2 t3)
_ -> raise ()
Cry.PC _ -> raise ()
importProp :: Prop -> Maybe [Cry.Prop]
importProp prop =
case prop of
PFalse -> Nothing
PTrue -> Just []
Not p -> importProp =<< pNot p
p1 :&& p2 -> do ps1 <- importProp p1
ps2 <- importProp p2
return (ps1 ++ ps2)
_ :|| _ -> Nothing
Fin expr -> do t <- importType expr
return [ Cry.pFin t ]
e1 :== e2 -> do t1 <- importType e1
t2 <- importType e2
return [t1 Cry.=#= t2]
e1 :>= e2 -> do t1 <- importType e1
t2 <- importType e2
return [t1 Cry.>== t2]
_ :> _ -> Nothing
e1 :==: e2 -> do t1 <- importType e1
t2 <- importType e2
-- XXX: Do we need to add fin?
return [t1 Cry.=#= t2]
_ :>: _ -> Nothing
where
pNot p =
case p of
PFalse -> Just PTrue
PTrue -> Nothing
Not a -> Just a
_ :&& _ -> Nothing
a :|| b -> Just (Not a :&& Not b)
Fin a -> Just (a :== K Inf)
_ :== _ -> Nothing
_ :>= _ -> Nothing
a :> b -> Just (b :>= a)
_ :==: _ -> Nothing
a :>: b -> Just (b :>= a)
-- XXX: Do we need to add Fin on `a` and 'b'?
importType :: Expr -> Maybe Cry.Type
importType = go
where
go expr =
case expr of
Var x -> case x of
UserName v -> return (Cry.TVar v)
_ -> Nothing
K n -> case n of
Nat x -> Just (Cry.tNum x)
Inf -> Just (Cry.tInf)
x :+ y -> op2 Cry.TCAdd x y
x :- y -> op2 Cry.TCSub x y
x :* y -> op2 Cry.TCMul x y
Div x y -> op2 Cry.TCDiv x y
Mod x y -> op2 Cry.TCMod x y
x :^^ y -> op2 Cry.TCExp x y
Min x y -> op2 Cry.TCMin x y
Max x y -> op2 Cry.TCMax x y
Width x -> op1 Cry.TCWidth x
LenFromThen x y z -> op3 Cry.TCLenFromThen x y z
LenFromThenTo x y z -> op3 Cry.TCLenFromThenTo x y z
app f xs = Cry.TCon (Cry.TF f) xs
op1 f x =
do t <- go x
return (app f [t])
op2 f x y =
do t1 <- go x
t2 <- go y
return (app f [t1,t2])
op3 f x y z =
do t1 <- go x
t2 <- go y
t3 <- go z
return (app f [t1,t2,t3])
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/Interval.hs 0000644 0000000 0000000 00000025715 12737220176 022516 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- An interval interpretation of types.
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE BangPatterns #-}
module Cryptol.TypeCheck.Solver.Numeric.Interval where
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Solver.InfNat
import Cryptol.Utils.PP hiding (int)
import Data.Map ( Map )
import qualified Data.Map as Map
import Data.Maybe (catMaybes)
-- | Only meaningful for numeric types
typeInterval :: Map TVar Interval -> Type -> Interval
typeInterval varInfo = go
where
go ty =
case ty of
TUser _ _ t -> go t
TCon tc ts ->
case (tc, ts) of
(TC TCInf, []) -> iConst Inf
(TC (TCNum n), []) -> iConst (Nat n)
(TF TCAdd, [x,y]) -> iAdd (go x) (go y)
(TF TCSub, [x,y]) -> iSub (go x) (go y)
(TF TCMul, [x,y]) -> iMul (go x) (go y)
(TF TCDiv, [x,y]) -> iDiv (go x) (go y)
(TF TCMod, [x,y]) -> iMod (go x) (go y)
(TF TCExp, [x,y]) -> iExp (go x) (go y)
(TF TCWidth, [x]) -> iWidth (go x)
(TF TCMin, [x,y]) -> iMin (go x) (go y)
(TF TCMax, [x,y]) -> iMax (go x) (go y)
(TF TCLenFromThen, [x,y,z]) ->
iLenFromThen (go x) (go y) (go z)
(TF TCLenFromThenTo, [x,y,z]) ->
iLenFromThenTo (go x) (go y) (go z)
_ -> iAny
TVar x -> Map.findWithDefault iAny x varInfo
_ -> iAny
data IntervalUpdate = NoChange
| InvalidInterval TVar
| NewIntervals (Map TVar Interval)
deriving (Show)
updateInterval :: (TVar,Interval) -> Map TVar Interval -> IntervalUpdate
updateInterval (x,int) varInts =
case Map.lookup x varInts of
Just int' ->
case iIntersect int int' of
Just val | int' /= val -> NewIntervals (Map.insert x val varInts)
| otherwise -> NoChange
Nothing -> InvalidInterval x
Nothing -> NewIntervals (Map.insert x int varInts)
computePropIntervals :: Map TVar Interval -> [Prop] -> IntervalUpdate
computePropIntervals ints ps0 = go (3 :: Int) False ints ps0
where
go !_n False _ [] = NoChange
go !n True is []
| n > 0 = changed is (go (n-1) False is ps0)
| otherwise = NewIntervals is
go !n new is (p:ps) =
case foldr (update is) NoChange (propInterval is p) of
InvalidInterval i -> InvalidInterval i
NewIntervals is' -> go n True is' ps
NoChange -> go n new is ps
changed a x = case x of
NoChange -> NewIntervals a
r -> r
update is0 int NoChange = updateInterval int is0
update _ _ (InvalidInterval i) = InvalidInterval i
update _ int (NewIntervals is) = changed is (updateInterval int is)
-- | What we learn about variables from a single prop.
propInterval :: Map TVar Interval -> Prop -> [(TVar,Interval)]
propInterval varInts prop = catMaybes
[ do ty <- pIsFin prop
x <- tIsVar ty
return (x,iAnyFin)
, do (l,r) <- pIsEq prop
x <- tIsVar l
return (x,typeInterval varInts r)
, do (l,r) <- pIsEq prop
x <- tIsVar r
return (x,typeInterval varInts l)
, do (l,r) <- pIsGeq prop
x <- tIsVar l
let int = typeInterval varInts r
return (x,int { iUpper = Just Inf })
, do (l,r) <- pIsGeq prop
x <- tIsVar r
let int = typeInterval varInts l
return (x,int { iLower = Nat 0 })
]
--------------------------------------------------------------------------------
data Interval = Interval
{ iLower :: Nat' -- ^ lower bound (inclusive)
, iUpper :: Maybe Nat' -- ^ upper bound (inclusive)
-- If there is no upper bound,
-- than all *natural* numbers.
} deriving (Eq,Show)
ppIntervals :: Map TVar Interval -> Doc
ppIntervals = vcat . map ppr . Map.toList
where
ppr (var,i) = pp var <> char ':' <+> ppInterval i
ppInterval :: Interval -> Doc
ppInterval x = brackets (hsep [ ppr (iLower x)
, text ".."
, maybe (text "fin") ppr (iUpper x)])
where
ppr a = case a of
Nat n -> integer n
Inf -> text "inf"
iIsExact :: Interval -> Maybe Nat'
iIsExact i = if iUpper i == Just (iLower i) then Just (iLower i) else Nothing
iIsFin :: Interval -> Bool
iIsFin i = case iUpper i of
Just Inf -> False
_ -> True
-- | Returns 'True' when the intervals definitely overlap, and 'False'
-- otherwise.
iDisjoint :: Interval -> Interval -> Bool
iDisjoint
(Interval (Nat l1) (Just (Nat h1)))
(Interval (Nat l2) (Just (Nat h2))) =
or [ h1 > l2 && h1 < h2, l1 > l2 && l1 < h2 ]
iDisjoint _ _ = False
-- | Intersect two intervals, yielding a new one that describes the space where
-- they overlap. If the two intervals are disjoint, the result will be
-- 'Nothing'.
iIntersect :: Interval -> Interval -> Maybe Interval
iIntersect i j =
case (lower,upper) of
(Nat l, Just (Nat u)) | l <= u -> ok
(Nat _, Just Inf) -> ok
(Nat _, Nothing) -> ok
(Inf, Just Inf) -> ok
_ -> Nothing
where
ok = Just (Interval lower upper)
lower = nMax (iLower i) (iLower j)
upper = case (iUpper i, iUpper j) of
(Just a, Just b) -> Just (nMin a b)
(Nothing,Nothing) -> Nothing
(Just l,Nothing) | l /= Inf -> Just l
(Nothing,Just r) | r /= Inf -> Just r
_ -> Nothing
-- | Any value
iAny :: Interval
iAny = Interval (Nat 0) (Just Inf)
-- | Any finite value
iAnyFin :: Interval
iAnyFin = Interval (Nat 0) Nothing
-- | Exactly this value
iConst :: Nat' -> Interval
iConst x = Interval x (Just x)
iAdd :: Interval -> Interval -> Interval
iAdd i j = Interval { iLower = nAdd (iLower i) (iLower j)
, iUpper = case (iUpper i, iUpper j) of
(Nothing, Nothing) -> Nothing
(Just x, Just y) -> Just (nAdd x y)
(Nothing, Just y) -> upper y
(Just x, Nothing) -> upper x
}
where
upper x = case x of
Inf -> Just Inf
_ -> Nothing
iMul :: Interval -> Interval -> Interval
iMul i j = Interval { iLower = nMul (iLower i) (iLower j)
, iUpper = case (iUpper i, iUpper j) of
(Nothing, Nothing) -> Nothing
(Just x, Just y) -> Just (nMul x y)
(Nothing, Just y) -> upper y
(Just x, Nothing) -> upper x
}
where
upper x = case x of
Inf -> Just Inf
Nat 0 -> Just (Nat 0)
_ -> Nothing
iExp :: Interval -> Interval -> Interval
iExp i j = Interval { iLower = nExp (iLower i) (iLower j)
, iUpper = case (iUpper i, iUpper j) of
(Nothing, Nothing) -> Nothing
(Just x, Just y) -> Just (nExp x y)
(Nothing, Just y) -> upperR y
(Just x, Nothing) -> upperL x
}
where
upperL x = case x of
Inf -> Just Inf
Nat 0 -> Just (Nat 0)
Nat 1 -> Just (Nat 1)
_ -> Nothing
upperR x = case x of
Inf -> Just Inf
Nat 0 -> Just (Nat 1)
_ -> Nothing
iMin :: Interval -> Interval -> Interval
iMin i j = Interval { iLower = nMin (iLower i) (iLower j)
, iUpper = case (iUpper i, iUpper j) of
(Nothing, Nothing) -> Nothing
(Just x, Just y) -> Just (nMin x y)
(Nothing, Just Inf) -> Nothing
(Nothing, Just y) -> Just y
(Just Inf, Nothing) -> Nothing
(Just x, Nothing) -> Just x
}
iMax :: Interval -> Interval -> Interval
iMax i j = Interval { iLower = nMax (iLower i) (iLower j)
, iUpper = case (iUpper i, iUpper j) of
(Nothing, Nothing) -> Nothing
(Just x, Just y) -> Just (nMax x y)
(Nothing, Just Inf) -> Just Inf
(Nothing, Just _) -> Nothing
(Just Inf, Nothing) -> Just Inf
(Just _, Nothing) -> Nothing
}
iSub :: Interval -> Interval -> Interval
iSub i j = Interval { iLower = lower, iUpper = upper }
where
lower = case iUpper j of
Nothing -> Nat 0
Just x -> case nSub (iLower i) x of
Nothing -> Nat 0
Just y -> y
upper = case iUpper i of
Nothing -> Nothing
Just x -> case nSub x (iLower j) of
Nothing -> Just Inf {- malformed subtraction -}
Just y -> Just y
iDiv :: Interval -> Interval -> Interval
iDiv i j = Interval { iLower = lower, iUpper = upper }
where
lower = case iUpper j of
Nothing -> Nat 0
Just x -> case nDiv (iLower i) x of
Nothing -> Nat 0 -- malformed division
Just y -> y
upper = case iUpper i of
Nothing -> Nothing
Just x -> case nDiv x (nMax (iLower i) (Nat 1)) of
Nothing -> Just Inf
Just y -> Just y
iMod :: Interval -> Interval -> Interval
iMod _ j = Interval { iLower = Nat 0, iUpper = upper }
where
upper = case iUpper j of
Just (Nat n) | n > 0 -> Just (Nat (n - 1))
_ -> Nothing
iWidth :: Interval -> Interval
iWidth i = Interval { iLower = nWidth (iLower i)
, iUpper = case iUpper i of
Nothing -> Nothing
Just n -> Just (nWidth n)
}
iLenFromThen :: Interval -> Interval -> Interval -> Interval
iLenFromThen i j w
| Just x <- iIsExact i, Just y <- iIsExact j, Just z <- iIsExact w
, Just r <- nLenFromThen x y z = iConst r
| otherwise =
case iUpper w of
Just (Nat n) ->
Interval { iLower = Nat 0, iUpper = Just (Nat (2^n - 1)) }
_ -> iAnyFin
iLenFromThenTo :: Interval -> Interval -> Interval -> Interval
iLenFromThenTo i j k
| Just x <- iIsExact i, Just y <- iIsExact j, Just z <- iIsExact k
, Just r <- nLenFromThenTo x y z = iConst r
| otherwise = iAnyFin
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/NonLin.hs 0000644 0000000 0000000 00000017430 12737220176 022122 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Separate Non-Linear Constraints
-- When we spot a non-linear expression, we name it and add it to a map.
--
-- If we see the same expression multiple times, then we give it the same name.
--
-- The body of the non-linear expression is not processed further,
-- so the resulting map should not contain any of the newly minted names.
{-# LANGUAGE Safe, RecordWildCards #-}
module Cryptol.TypeCheck.Solver.Numeric.NonLin
( nonLinProp
, NonLinS, nonLinSubst
, initialNonLinS
, apSubstNL
, lookupNL
) where
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.TypeCheck.Solver.Numeric.Simplify
import Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr
import Cryptol.Utils.Panic(panic)
-- import Data.GenericTrie (Trie)
-- import qualified Data.GenericTrie as Trie
import Data.Maybe ( fromMaybe )
import MonadLib
import Data.Map (Map)
import qualified Data.Map as Map
type Trie = Map
trie_empty :: Map k a
trie_empty = Map.empty
trie_insert :: Expr -> a -> Map Expr a -> Map Expr a
trie_insert = Map.insert
trie_delete :: Expr -> Map Expr a -> Map Expr a
trie_delete = Map.delete
trie_lookup :: Expr -> Map Expr a -> Maybe a
trie_lookup = Map.lookup
-- | Factor-out non-linear terms, by naming them.
nonLinProp :: NonLinS -> Prop -> ([Prop], NonLinS)
nonLinProp s0 prop = (p : ps, s)
where ((p,ps),s) = runNL s0 (nonLinPropM prop)
{- | Apply a substituin to the non-linear expression database.
Returns `Nothing` if nothing was affected.
Otherwise returns `Just`, and a substitution for non-linear expressions
that became linear.
The definitions of NL terms do not contain other named NL terms,
so it does not matter if the substitution contains bindings like @_a = e@.
There should be no bindings that mention NL term names in the definitions
of the substition (i.e, things like @x = _a@ are NOT ok).
-}
apSubstNL :: Subst -> NonLinS -> Maybe (Subst, [Prop], NonLinS)
apSubstNL su s0 = case runNL s0 (mApSubstNL su) of
((Nothing,_),_) -> Nothing
((Just su1,ps),r) -> Just (su1,ps,r)
lookupNL :: Name -> NonLinS -> Maybe Expr
lookupNL x NonLinS { .. } = Map.lookup x nonLinExprs
runNL :: NonLinS -> NonLinM a -> ((a, [Prop]), NonLinS)
runNL s m = runId
$ runStateT s
$ do a <- m
ps <- finishTodos
return (a,ps)
-- | Get the known non-linear terms.
nonLinSubst :: NonLinS -> Subst
nonLinSubst = nonLinExprs
-- | The initial state for the linearization process.
initialNonLinS :: NonLinS
initialNonLinS = NonLinS
{ nextName = 0
, nonLinExprs = Map.empty
, nlKnown = trie_empty
, nlTodo = []
}
data SubstOneRes = NoChange
-- ^ Substitution does not affect the expression.
| Updated (Maybe (Name,Expr))
-- ^ The expression was updated and, maybe, it became linear.
{- | Apply the substituint to all non-linear bindings.
Returns `Nothing` if nothing was affected.
Otherwise returns `Just`, and a substituion mapping names that used
to be non-linear but became linear.
Note that we may return `Just empty`, indicating that some non-linear
expressions were updated, but they remained non-linear. -}
mApSubstNL :: Subst -> NonLinM (Maybe Subst)
mApSubstNL su =
do s <- get
answers <- mapM (mApSubstOneNL su) (Map.toList (nonLinExprs s))
return (foldr upd Nothing answers)
where
upd NoChange ch = ch
upd (Updated mb) ch = let lsu = fromMaybe Map.empty ch
in Just (case mb of
Nothing -> lsu
Just (x,e) -> Map.insert x e lsu)
mApSubstOneNL :: Subst -> (Name,Expr) -> NonLinM SubstOneRes
mApSubstOneNL su (x,e) =
case apSubst su e of
Nothing -> return NoChange
Just e1 ->
case crySimpExprMaybe e1 of
Nothing ->
sets $ \NonLinS { .. } ->
( Updated Nothing
, NonLinS { nonLinExprs = Map.insert x e1 nonLinExprs
, nlKnown = trie_insert e1 x (trie_delete e nlKnown)
, .. }
)
Just e2
| isNonLinOp e2 ->
sets $ \NonLinS { .. } ->
(Updated Nothing
, NonLinS { nonLinExprs = Map.insert x e2 nonLinExprs
, nlKnown = trie_insert e2 x (trie_delete e nlKnown)
, .. }
)
| otherwise ->
do sets_ $ \NonLinS { .. } ->
NonLinS { nonLinExprs = Map.delete x nonLinExprs
, nlKnown = trie_delete e nlKnown
, ..
}
es <- mapM nonLinExprM (cryExprExprs e2)
let e3 = cryRebuildExpr e2 es
return (Updated (Just (x,e3)))
-- | Is the top-level operator a non-linear one.
isNonLinOp :: Expr -> Bool
isNonLinOp expr =
case expr of
K _ -> False
Var _ -> False
_ :+ _ -> False
_ :- _ -> False
x :* y ->
case (x,y) of
(K _, _) -> False
(_, K _) -> False
_ -> True
Div _ y ->
case y of
K (Nat n) -> n == 0
_ -> True
Mod _ y ->
case y of
K (Nat n) -> n == 0
_ -> True
_ :^^ _ -> True
Min _ _ -> False
Max _ _ -> False
Width _ -> True
LenFromThen _ _ _ -> True -- See also comment on `LenFromThenTo`
LenFromThenTo x y _ ->
case (x,y) of
(K _, K _) -> False
_ -> True -- Actually, as long as the difference bettwen
-- `x` and `y` is constant we'd be OK, but not
-- sure how to do that...
nlImplied :: Expr -> Name -> [Prop]
nlImplied expr x =
map crySimplify $
case expr of
K (Nat n) :^^ e | n >= 2 -> [ Var x :>= one, Var x :>= e :+ one ]
Mod _ e -> [ e :>= Var x :+ one ]
_ -> []
nonLinPropM :: Prop -> NonLinM Prop
nonLinPropM prop =
case prop of
PFalse -> return PFalse
PTrue -> return PTrue
Not p -> Not `fmap` nonLinPropM p
p :&& q -> (:&&) `fmap` nonLinPropM p `ap` nonLinPropM q
p :|| q -> (:||) `fmap` nonLinPropM p `ap` nonLinPropM q
Fin (Var _) -> return prop
Fin _ -> unexpected
x :==: y -> (:==:) `fmap` nonLinExprM x `ap` nonLinExprM y
x :>: y -> (:>:) `fmap` nonLinExprM x `ap` nonLinExprM y
_ :== _ -> unexpected
_ :>= _ -> unexpected
_ :> _ -> unexpected
where
unexpected = panic "nonLinPropM" [ show (ppProp prop) ]
nonLinExprM :: Expr -> NonLinM Expr
nonLinExprM expr
| isNonLinOp expr = nameExpr expr
| otherwise = cryRebuildExpr expr `fmap` mapM nonLinExprM (cryExprExprs expr)
type NonLinM = StateT NonLinS Id
data NonLinS = NonLinS
{ nextName :: !Int
, nonLinExprs :: Subst
, nlKnown :: Trie Expr Name
, nlTodo :: [Prop]
} deriving Show
nameExpr :: Expr -> NonLinM Expr
nameExpr e = sets $ \s ->
case trie_lookup e (nlKnown s) of
Just x -> (Var x, s)
Nothing ->
let x = nextName s
n = SysName x
s1 = NonLinS { nextName = 1 + x
, nonLinExprs = Map.insert n e (nonLinExprs s)
, nlKnown = trie_insert e n (nlKnown s)
, nlTodo = nlImplied e n ++ nlTodo s
}
in (Var n, s1)
finishTodos :: NonLinM [Prop]
finishTodos =
do s <- get
case nlTodo s of
[] -> return []
p : ps ->
do set s { nlTodo = ps }
p' <- nonLinPropM p
ps' <- finishTodos
return (p' : ps')
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/Simplify.hs 0000644 0000000 0000000 00000061426 12737220176 022525 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- TODO:
-- - Putting in a normal form to spot "prove by assumption"
-- - Additional simplification rules, namely various cancelation.
-- - Things like: lg2 e(x) = x, where we know thate is increasing.
{-# LANGUAGE Safe, PatternGuards, BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
module Cryptol.TypeCheck.Solver.Numeric.Simplify
(
-- * Simplify a property
crySimplify, crySimplifyMaybe
-- * Simplify expressions in a prop
, crySimpPropExpr, crySimpPropExprMaybe
) where
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr
import Cryptol.TypeCheck.Solver.InfNat(genLog,genRoot,rootExact)
import Cryptol.Utils.Misc ( anyJust )
import Control.Monad ( mplus )
import Data.List ( sortBy )
import Data.Maybe ( fromMaybe )
import qualified Data.Set as Set
-- | Simplify a property, if possible.
crySimplify :: Prop -> Prop
crySimplify p = fromMaybe p (crySimplifyMaybe p)
-- | Simplify a property, if possible.
crySimplifyMaybe :: Prop -> Maybe Prop
crySimplifyMaybe p =
let mbSimpExprs = simpSubs p
exprsSimped = fromMaybe p mbSimpExprs
mbRearrange = tryRearrange exprsSimped
rearranged = fromMaybe exprsSimped mbRearrange
in crySimplify `fmap` (crySimpStep rearranged `mplus` mbRearrange
`mplus` mbSimpExprs)
where
tryRearrange q = case q of
_ :&& _ -> cryRearrangeAnd q
_ :|| _ -> cryRearrangeOr q
_ -> Nothing
simpSubs q = case q of
Not a -> Not `fmap` crySimplifyMaybe a
a :&& b -> do [a',b'] <- anyJust crySimplifyMaybe [a,b]
return (a' :&& b')
a :|| b -> do [a',b'] <- anyJust crySimplifyMaybe [a,b]
return (a' :|| b')
_ -> crySimpPropExprMaybe q
-- | A single simplification step.
crySimpStep :: Prop -> Maybe Prop
crySimpStep prop =
case prop of
Fin x -> cryIsFin x -- Fin only on variables.
x :== y -> Just (cryIsEq x y)
x :> y -> Just (cryIsGt x y)
x :>= y ->
case (x,y) of
-- XXX: DUPLICTION
(K (Nat 0), _) -> Just (y :== zero)
(K (Nat a), Width b) -> Just (K (Nat (2 ^ a)) :>= b)
(_, K (Nat 0)) -> Just PTrue
(Width e, K (Nat b)) -> Just (e :>= K (Nat (2^(b-1))))
(K Inf, _) -> Just PTrue
(_, K Inf) -> Just (x :== inf)
_ -> Just (x :== inf :|| one :+ x :> y)
x :==: y ->
case (x,y) of
(K a, K b) -> Just (if a == b then PTrue else PFalse)
(K (Nat n), _) | Just p <- cryIsNat True n y -> Just p
(_, K (Nat n)) | Just p <- cryIsNat True n x -> Just p
_ | x == y -> Just PTrue
| otherwise -> case (x,y) of
(Var _, _) -> Nothing
(_, Var _) -> Just (y :==: x)
_ -> Nothing
x :>: y ->
case (x,y) of
(K (Nat n),_) | Just p <- cryNatGt True n y -> Just p
(_, K (Nat n)) | Just p <- cryGtNat True n x -> Just p
_ | x == y -> Just PFalse
| otherwise -> Nothing
-- For :&& and :|| we assume that the props have been rearrnaged
p :&& q -> cryAnd p q
p :|| q -> cryOr p q
Not p -> cryNot p
PFalse -> Nothing
PTrue -> Nothing
-- | Rebalance parens, and arrange conjucts so that we can transfer
-- information left-to-right.
cryRearrangeAnd :: Prop -> Maybe Prop
cryRearrangeAnd prop =
case rebalance prop of
Just p -> Just p
Nothing -> cryAnds `fmap` cryRearrange cmpAnd (split prop)
where
rebalance (a :&& b) =
case a of
PFalse -> Just PFalse
PTrue -> Just b
a1 :&& a2 -> Just (a1 :&& (a2 :&& b))
_ -> fmap (a :&&) (rebalance b)
rebalance _ = Nothing
split (a :&& b) = a : split b
split a = [a]
-- | Rebalance parens, and arrange disjuncts so that we can transfer
-- information left-to-right.
cryRearrangeOr :: Prop -> Maybe Prop
cryRearrangeOr prop =
case rebalance prop of
Just p -> Just p
Nothing -> cryOrs `fmap` cryRearrange cmpOr (split prop)
where
rebalance (a :|| b) =
case a of
PFalse -> Just b
PTrue -> Just PTrue
a1 :|| a2 -> Just (a1 :|| (a2 :|| b))
_ -> fmap (a :||) (rebalance b)
rebalance _ = Nothing
split (a :|| b) = a : split b
split a = [a]
-- | Identify propositions that are suiatable for inlining.
cryIsDefn :: Prop -> Maybe (Name, Expr)
cryIsDefn (Var x :==: e) = if (x `Set.member` cryExprFVS e)
then Nothing
else Just (x,e)
cryIsDefn _ = Nothing
type PropOrdering = (Int,Prop) -> (Int,Prop) -> Ordering
{- | Rearrange proposition for conjuctions and disjunctions.
information left-to-right, so we put proposition with information content
on the left.
-}
cryRearrange :: PropOrdering -> [Prop] -> Maybe [Prop]
cryRearrange cmp ps = if ascending keys then Nothing else Just sortedProps
where
-- We tag each proposition with a number, so that later we can tell easily
-- if the propositions got rearranged.
(keys, sortedProps) = unzip (sortBy cmp (zip [ 0 :: Int .. ] ps))
ascending (x : y : zs) = x < y && ascending (y : zs)
ascending _ = True
cmpAnd :: PropOrdering
cmpAnd (k1,prop1) (k2,prop2) =
case (prop1, prop2) of
-- First comes PFalse, maybe we don't need to do anything
(PFalse, PFalse) -> compare k1 k2
(PFalse, _) -> LT
(_,PFalse) -> GT
-- Next comes PTrue
(PTrue, PTrue) -> compare k1 k2
(PTrue, _) -> LT
(_,PTrue) -> GT
-- Next come `not (fin a)` (i.e, a = inf)
(Not (Fin (Var x)), Not (Fin (Var y))) -> cmpVars x y
(Not (Fin (Var _)), _) -> LT
(_, Not (Fin (Var _))) -> GT
-- Next come defintions: `x = e` (with `x` not in `fvs e`)
-- XXX: Inefficient, because we keep recomputing free variables
-- (here, and then when actually applying the substitution)
_ | Just (x,_) <- mbL
, Just (y,_) <- mbR -> cmpVars x y
| Just _ <- mbL -> LT
| Just _ <- mbR -> GT
where
mbL = cryIsDefn prop1
mbR = cryIsDefn prop2
-- Next come `fin a`
(Fin (Var x), Fin (Var y)) -> cmpVars x y
(Fin (Var _), _) -> LT
(_, Fin (Var _)) -> GT
-- Everything else stays as is
_ -> compare k1 k2
where
cmpVars x y
| x < y = LT
| x > y = GT
| otherwise = compare k1 k2
cmpOr :: PropOrdering
cmpOr (k1,prop1) (k2,prop2) =
case (prop1, prop2) of
-- First comes PTrue, maybe we don't need to do anything
(PTrue, PTrue) -> compare k1 k2
(PTrue, _) -> LT
(_,PTrue) -> GT
-- Next comes PFalse
(PFalse, PFalse) -> compare k1 k2
(PFalse, _) -> LT
(_,PFalse) -> GT
-- Next comes `fin a` (because we propagete `a = inf`)
(Fin (Var x), Fin (Var y)) -> cmpVars x y
(Fin (Var _), _) -> LT
(_, Fin (Var _)) -> GT
-- Next come `not (fin a)` (i.e, propagete (fin a))
(Not (Fin (Var x)), Not (Fin (Var y))) -> cmpVars x y
(Not (Fin (Var _)), _) -> LT
(_, Not (Fin (Var _))) -> GT
-- we don't propagete (x /= e) for now.
-- Everything else stays as is
_ -> compare k1 k2
where
cmpVars x y
| x < y = LT
| x > y = GT
| otherwise = compare k1 k2
-- | Simplification of ':&&'.
-- Assumes arranged conjucntions.
-- See 'cryRearrangeAnd'.
cryAnd :: Prop -> Prop -> Maybe Prop
cryAnd p q =
case p of
PTrue -> Just q
PFalse -> Just PFalse
Not (Fin (Var x))
| Just q' <- cryKnownFin x False q -> Just (p :&& q')
Fin (Var x)
| Just q' <- cryKnownFin x True q -> Just (p :&& q')
_ | Just (x,e) <- cryIsDefn p
, Just q' <- cryLet x e q
-> Just (p :&& q')
_ -> Nothing
-- | Simplification of ':||'.
-- Assumes arranged disjunctions.
-- See 'cryRearrangeOr'
cryOr :: Prop -> Prop -> Maybe Prop
cryOr p q =
case p of
PTrue -> Just PTrue
PFalse -> Just q
Fin (Var x)
| Just q' <- cryKnownFin x False q -> Just (p :|| q')
Not (Fin (Var x))
| Just q' <- cryKnownFin x True q -> Just (p :|| q')
_ -> Nothing
-- | Propagate the fact that the variable is known to be finite ('True')
-- or not-finite ('False').
-- Note that this may introduce new expression redexes.
cryKnownFin :: Name -> Bool -> Prop -> Maybe Prop
cryKnownFin a isFin prop =
case prop of
Fin (Var a') | a == a' -> Just (if isFin then PTrue else PFalse)
p :&& q -> do [p',q'] <- anyJust (cryKnownFin a isFin) [p,q]
return (p' :&& q')
p :|| q -> do [p',q'] <- anyJust (cryKnownFin a isFin) [p,q]
return (p' :|| q')
Not p -> Not `fmap` cryKnownFin a isFin p
x :==: y
| not isFin, Just [x',y'] <- anyJust (cryLet a inf) [x,y]
-> Just (cryNatOp (:==:) x' y')
x :>: y
| not isFin, Just [x',y'] <- anyJust (cryLet a inf) [x,y]
-> Just (cryNatOp (:>:) x' y')
-- All the other cases should be simplified, eventually.
_ -> Nothing
-- | Negation.
cryNot :: Prop -> Maybe Prop
cryNot prop =
case prop of
Fin _ -> Nothing
x :== y -> Just (x :> y :|| y :> x)
x :>= y -> Just (y :> x)
x :> y -> Just (y :>= x)
x :==: y -> Just (x :>: y :|| y :>: x)
_ :>: _ -> Nothing
p :&& q -> Just (Not p :|| Not q)
p :|| q -> Just (Not p :&& Not q)
Not p -> Just p
PFalse -> Just PTrue
PTrue -> Just PFalse
-- | Simplificaiton for @:==@
cryIsEq :: Expr -> Expr -> Prop
cryIsEq l r =
case (l,r) of
(K m, K n) -> if m == n then PTrue else PFalse
(K Inf, _) -> Not (Fin r)
(_, K Inf) -> Not (Fin l)
(Div x y, z) -> x :>= z :* y :&& (one :+ z) :* y :> x
(K (Nat n),_) | Just p <- cryIsNat False n r -> p
(_,K (Nat n)) | Just p <- cryIsNat False n l -> p
_ -> Not (Fin l) :&& Not (Fin r)
:|| Fin l :&& Fin r :&& cryNatOp (:==:) l r
-- | Simplificatoin for @:>@
cryIsGt :: Expr -> Expr -> Prop
cryIsGt (K m) (K n) = if m > n then PTrue else PFalse
cryIsGt (K (Nat n)) e | Just p <- cryNatGt False n e = p
cryIsGt e (K (Nat n)) | Just p <- cryGtNat False n e = p
cryIsGt x y = Fin y :&& (x :== inf :||
Fin x :&& cryNatOp (:>:) x y)
-- | Attempt to simplify a @fin@ constraint.
-- Assumes a defined input.
cryIsFin :: Expr -> Maybe Prop
cryIsFin expr =
case expr of
K Inf -> Just PFalse
K (Nat _) -> Just PTrue
Var _ -> Nothing
t1 :+ t2 -> Just (Fin t1 :&& Fin t2)
t1 :- _ -> Just (Fin t1)
t1 :* t2 -> Just ( Fin t1 :&& Fin t2
:|| t1 :== zero :&& t2 :== inf
:|| t2 :== zero :&& t1 :== inf
)
Div t1 _ -> Just (Fin t1)
Mod _ _ -> Just PTrue
t1 :^^ t2 ->
Just ( Fin t1 :&& Fin t2
:|| t1 :== inf :&& t2 :== zero -- inf ^^ 0
:|| t2 :== inf :&& (t1 :== zero :|| t1 :== one)
-- 0 ^^ inf, 1 ^^ inf
)
Min t1 t2 -> Just (Fin t1 :|| Fin t2)
Max t1 t2 -> Just (Fin t1 :&& Fin t2)
Width t1 -> Just (Fin t1)
LenFromThen _ _ _ -> Just PTrue
LenFromThenTo _ _ _ -> Just PTrue
cryIsNat :: Bool -> Integer -> Expr -> Maybe Prop
cryIsNat useFinite n expr =
case expr of
K Inf -> Just PFalse
K (Nat m) -> Just (if m == n then PTrue else PFalse)
Var _ | useFinite -> Nothing
| otherwise -> Just (Fin expr :&& expr :==: K (Nat n))
K (Nat m) :+ e2 -> Just $ if m > n then PFalse
else eq e2 $ K $ Nat $ n - m
x :+ y
| n == 0 -> Just (eq x zero :&& eq y zero)
| n == 1 -> Just (eq x zero :&& eq y one :||
eq x one :&& eq y zero)
| otherwise -> Nothing
e1 :- e2 -> Just $ eq (K (Nat n) :+ e2) e1
K (Nat m) :* e2 ->
Just $ if m == 0
then if n == 0 then PTrue else PFalse
else case divMod n m of
(q,r) -> if r == 0 then eq e2 (K (Nat q))
else PFalse
e1 :* e2
| n == 0 -> Just (eq e1 zero :|| eq e2 zero)
| n == 1 -> Just (eq e1 one :&& eq e2 one)
| otherwise -> Nothing
-- (x >= n * y) /\ ((n+1) * y > x)
Div x y -> Just (gt (one :+ x) (K (Nat n) :* y) :&&
gt (K (Nat (n + 1)) :* y) x)
Mod _ _ | useFinite -> Nothing
| otherwise -> Just (cryNatOp (:==:) expr (K (Nat n)))
K (Nat m) :^^ y -> Just $ case genLog n m of
Just (a, exact)
| exact -> eq y (K (Nat a))
_ -> PFalse
x :^^ K (Nat m) -> Just $ case rootExact n m of
Just a -> eq x (K (Nat a))
Nothing -> PFalse
x :^^ y
| n == 0 -> Just (eq x zero :&& gt y zero)
| n == 1 -> Just (eq x one :|| eq y zero)
| otherwise -> Nothing
Min x y
| n == 0 -> Just (eq x zero :|| eq y zero)
| otherwise -> Just ( eq x (K (Nat n)) :&& gt y (K (Nat (n - 1)))
:|| eq y (K (Nat n)) :&& gt x (K (Nat (n - 1)))
)
Max x y -> Just ( eq x (K (Nat n)) :&& gt (K (Nat (n + 1))) y
:|| eq y (K (Nat n)) :&& gt (K (Nat (n + 1))) y
)
Width x
| n == 0 -> Just (eq x zero)
| otherwise -> Just (gt x (K (Nat (2^(n-1) - 1))) :&&
gt (K (Nat (2 ^ n))) x)
LenFromThen x y w
| n == 0 -> Just PFalse
-- See Note [Sequences of Length 1] in 'Cryptol.TypeCheck.Solver.InfNat'
| n == 1 -> Just (gt y x :&& gt (y :+ one) (two :^^ w))
| otherwise -> Nothing -- XXX: maybe some more?
-- See `nLenFromThenTo` in 'Cryptol.TypeCheck.Solver.InfNat'
LenFromThenTo x y z
| n == 0 -> Just ( gt x y :&& gt z x
:|| gt y x :&& gt x z
)
-- See Note [Sequences of Length 1] in 'Cryptol.TypeCheck.Solver.InfNat'
| n == 1 -> Just (gt z y :&& gt (x :+ one) z :||
gt y z :&& gt (z :+ one) x)
| otherwise -> Nothing -- XXX: maybe some more?
where
eq x y = if useFinite then x :==: y else x :== y
gt x y = if useFinite then x :>: y else x :> y
-- | Constant > expression
cryNatGt :: Bool -> Integer -> Expr -> Maybe Prop
cryNatGt useFinite n expr
| n == 0 = Just PFalse
| n == 1 = Just (eq expr zero)
| otherwise =
case expr of
K x -> Just $ if Nat n > x then PTrue else PFalse
Var _ -> Nothing
K (Nat m) :+ y -> Just $ if n >= m then gt (k (n - m)) y else PFalse
_ :+ _ -> Nothing
x :- y -> Just $ gt (k n :+ y) x
K (Nat m) :* y
| m == 0 -> Just PTrue -- because we know that n > 1
| otherwise -> Just $ case divMod n m of
(q,0) -> gt (k q) y
(0,_) -> eq y zero
(q,_) -> gt (k (q + 1)) y
_ :* _ -> Nothing
Div x y -> Just $ gt (k n :* y) x
Mod _ (K (Nat m))
| m <= n -> Just PTrue
Mod (K (Nat m)) _
| m < n -> Just PTrue
Mod _ _ -> Nothing
K (Nat m) :^^ y
| m == 0 -> Just PTrue -- because n > 1
| m == 1 -> Just PTrue -- ditto
| otherwise -> do (a,exact) <- genLog n m
return $ if exact
then gt (k a) y
else gt (k (a + 1)) y
x :^^ K (Nat m)
| m == 0 -> Just PTrue
| m == 1 -> Just (gt (k n) x)
| otherwise -> do (a,exact) <- genRoot n m
return $ if exact
then gt (k a) x
else gt (k (a + 1)) x
_ :^^ _ -> Nothing
Min x y -> Just $ gt (k n) x :|| gt (k n) y
Max x y -> Just $ gt (k n) x :&& gt (k n) y
Width x -> Just $ gt (k (2 ^ n)) x
LenFromThen _ _ _ -> Nothing -- Are there some rules?
LenFromThenTo _ _ _ -> Nothing -- Are there some rulesj
where
k x = K (Nat x)
eq x y = if useFinite then x :==: y else x :== y
gt x y = if useFinite then x :>: y else x :> y
-- | Expression > constant
cryGtNat :: Bool -> Integer -> Expr -> Maybe Prop
cryGtNat useFinite n expr =
case expr of
K x -> Just $ if x > Nat n then PTrue else PFalse
Var _ -> Nothing
K (Nat m) :+ y
| m > n -> Just PTrue
| otherwise -> Just (gt y (K (Nat (n - m))))
x :+ y
| n == 0 -> Just (gt x zero :|| gt y zero)
| otherwise -> Nothing
x :- y -> Just $ gt x (K (Nat n) :+ y)
K (Nat m) :* y
| m > 0 -> Just $ case divMod n m of
(a,_) -> gt y $ K $ Nat a
x :* y
| n == 0 -> Just (gt x zero :&& gt y zero)
| otherwise -> Nothing
Div x y -> Just $ gt (one :+ x) (K (Nat (n+1)) :* y)
Mod _ (K (Nat m))
| m <= n -> Just PFalse
Mod (K (Nat m)) _
| m < n -> Just PFalse
Mod _ _ -> Nothing
K (Nat m) :^^ y
| m == 0 -> Just $ if n == 0 then eq y zero else PFalse
| m == 1 -> Just $ if n == 0 then PTrue else PFalse
| otherwise -> do (a,_exact) <- genLog n m
Just (gt y (K (Nat a)))
x :^^ K (Nat m)
| m == 0 -> Just $ if n == 0 then PTrue else PFalse
| m == 1 -> Just $ gt x (K (Nat n))
| otherwise -> do (a,exact) <- genRoot n m
Just $ if exact
then gt x (K (Nat a))
else gt (one :+ x) (K (Nat (a+1)))
x :^^ y
| n == 0 -> Just (gt x zero :|| eq y zero)
| otherwise -> Nothing
Min x y -> Just $ gt x (K (Nat n)) :&& gt y (K (Nat n))
Max x y -> Just $ gt x (K (Nat n)) :|| gt y (K (Nat n))
Width x -> Just $ gt (one :+ x) (K (Nat (2 ^ n)))
LenFromThen _ _ _
| n == 0 -> Just PTrue
| otherwise -> Nothing -- Are there some rules?
LenFromThenTo x y z
| n == 0 -> Just (gt x y :&& gt z x :|| gt y x :&& gt x z)
| otherwise -> Nothing
where
eq x y = if useFinite then x :==: y else x :== y
gt x y = if useFinite then x :>: y else x :> y
-- | Simplify only the Expr parts of a Prop.
crySimpPropExpr :: Prop -> Prop
crySimpPropExpr p = fromMaybe p (crySimpPropExprMaybe p)
-- | Simplify only the Expr parts of a Prop.
-- Returns `Nothing` if there were no changes.
crySimpPropExprMaybe :: Prop -> Maybe Prop
crySimpPropExprMaybe prop =
case prop of
Fin e -> Fin `fmap` crySimpExprMaybe e
a :== b -> binop crySimpExprMaybe (:== ) a b
a :>= b -> binop crySimpExprMaybe (:>= ) a b
a :> b -> binop crySimpExprMaybe (:> ) a b
a :==: b -> binop crySimpExprMaybe (:==:) a b
a :>: b -> binop crySimpExprMaybe (:>: ) a b
a :&& b -> binop crySimpPropExprMaybe (:&&) a b
a :|| b -> binop crySimpPropExprMaybe (:||) a b
Not p -> Not `fmap` crySimpPropExprMaybe p
PFalse -> Nothing
PTrue -> Nothing
where
binop simp f l r =
case (simp l, simp r) of
(Nothing,Nothing) -> Nothing
(l',r') -> Just (f (fromMaybe l l') (fromMaybe r r'))
-- | Our goal is to bubble @inf@ terms to the top of @Return@.
cryNoInf :: Expr -> IfExpr Expr
cryNoInf expr =
case expr of
-- These are the interesting cases where we have to branch
x :* y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(K Inf, K Inf) -> return inf
(K Inf, _) -> mkIf (y' :==: zero) (return zero) (return inf)
(_, K Inf) -> mkIf (x' :==: zero) (return zero) (return inf)
_ -> return (x' :* y')
x :^^ y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(K Inf, K Inf) -> return inf
(K Inf, _) -> mkIf (y' :==: zero) (return one) (return inf)
(_, K Inf) -> mkIf (x' :==: zero) (return zero)
$ mkIf (x' :==: one) (return one)
$ return inf
_ -> return (x' :^^ y')
-- The rest just propagates
K _ -> return expr
Var _ -> return expr
x :+ y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(K Inf, _) -> return inf
(_, K Inf) -> return inf
_ -> return (x' :+ y')
x :- y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(_, K Inf) -> Impossible
(K Inf, _) -> return inf
_ -> mkIf (x' :==: y)
(return zero)
(mkIf (x' :>: y) (return (x' :- y'))
Impossible)
Div x y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(K Inf, _) -> Impossible
(_, K Inf) -> return zero
_ -> mkIf (y' :>: zero) (return (Div x' y')) Impossible
Mod x y ->
do x' <- cryNoInf x
-- `Mod x y` is finite, even if `y` is `inf`, so first check
-- for finiteness.
mkIf (Fin y)
(do y' <- cryNoInf y
case (x',y') of
(K Inf, _) -> Impossible
(_, K Inf) -> Impossible
_ -> mkIf (y' :>: zero) (return (Mod x' y')) Impossible
)
(return x')
Min x y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x',y') of
(K Inf, _) -> return y'
(_, K Inf) -> return x'
_ -> return (Min x' y')
Max x y ->
do x' <- cryNoInf x
y' <- cryNoInf y
case (x', y') of
(K Inf, _) -> return inf
(_, K Inf) -> return inf
_ -> return (Max x' y')
Width x ->
do x' <- cryNoInf x
case x' of
K Inf -> return inf
_ -> return (Width x')
LenFromThen x y w -> fun3 LenFromThen x y w
LenFromThenTo x y z -> fun3 LenFromThenTo x y z
where
fun3 f x y z =
do x' <- cryNoInf x
y' <- cryNoInf y
z' <- cryNoInf z
case (x',y',z') of
(K Inf, _, _) -> Impossible
(_, K Inf, _) -> Impossible
(_, _, K Inf) -> Impossible
_ -> mkIf (x' :==: y') Impossible
(return (f x' y' z'))
mkIf p t e = case crySimplify p of
PTrue -> t
PFalse -> e
p' -> If p' t e
-- | Make an expression that should work ONLY on natural nubers.
-- Eliminates occurances of @inf@.
-- Assumes that the two input expressions are well-formed and finite.
-- The expression is constructed by the given function.
cryNatOp :: (Expr -> Expr -> Prop) -> Expr -> Expr -> Prop
cryNatOp op x y =
toProp $
do x' <- noInf x
y' <- noInf y
return (op x' y')
where
noInf a = do a' <- cryNoInf a
case a' of
K Inf -> Impossible
_ -> return a'
toProp ite =
case ite of
Impossible -> PFalse -- It doesn't matter, but @false@ might anihilate.
Return p -> p
If p t e -> p :&& toProp t :|| Not p :&& toProp e
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/Simplify1.hs 0000644 0000000 0000000 00000035432 12737220176 022604 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Simplification.
-- The rules in this module are all conditional on the expressions being
-- well-defined.
--
-- So, for example, consider the formula `P`, which corresponds to `fin e`.
-- `P` says the following:
--
-- if e is well-formed, then will evaluate to a finite natural number.
--
-- More concretely, consider `fin (3 - 5)`. This will be simplified to `True`,
-- which does not mean that `3 - 5` is actually finite.
{-# LANGUAGE Safe, PatternGuards, BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
module Cryptol.TypeCheck.Solver.Numeric.Simplify1 (propToProp', ppProp') where
import Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr
(crySimpExpr, splitSum, normSum, Sign(..))
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.TypeCheck.Solver.InfNat(genLog,rootExact)
import Cryptol.Utils.Misc ( anyJust )
import Cryptol.Utils.Panic
import Cryptol.Utils.PP
import Control.Monad ( liftM2 )
import Data.Maybe ( fromMaybe )
import qualified Data.Map as Map
import Data.Either(partitionEithers)
data Atom = AFin Name
| AGt Expr Expr -- on naturals
| AEq Expr Expr -- on naturals
deriving Eq
type I = IfExpr' Atom
-- tmp
propToProp' :: Prop -> I Bool
propToProp' prop =
case prop of
Fin e -> pFin e
x :== y -> pEq x y
x :>= y -> pGeq x y
x :> y -> pGt x y
x :>: y -> pAnd (pFin x) (pAnd (pFin y) (pGt x y))
x :==: y -> pAnd (pFin x) (pAnd (pFin y) (pEq x y))
p :&& q -> pAnd (propToProp' p) (propToProp' q)
p :|| q -> pOr (propToProp' p) (propToProp' q)
Not p -> pNot (propToProp' p)
PFalse -> pFalse
PTrue -> pTrue
instance (Eq a, HasVars a) => HasVars (I a) where
apSubst su prop =
case prop of
Impossible -> Nothing
Return _ -> Nothing
If a t e ->
case apSubstAtom su a of
Nothing -> do [x,y] <- branches
return (If a x y)
Just a' -> Just $ fromMaybe (pIf a' t e)
$ do [x,y] <- branches
return (pIf a' x y)
where branches = anyJust (apSubst su) [t,e]
-- | Apply a substituition to an atom
apSubstAtom :: Subst -> Atom -> Maybe (I Bool)
apSubstAtom su atom =
case atom of
AFin x -> do e <- Map.lookup x su
return (pFin e)
AEq e1 e2 -> do [x,y] <- anyJust (apSubst su) [e1,e2]
return (pEq x y)
AGt e1 e2 -> do [x,y] <- anyJust (apSubst su) [e1,e2]
return (pGt x y)
{- TODO: Unused
-- | The various way in which the given proposition may be true.
-- The Boolean indicates if the atom is +ve:
-- 'True' for positive, 'False' for -ve.
truePaths :: I Bool -> [ [(Bool,Atom)] ]
truePaths prop =
case prop of
Impossible -> []
Return False -> []
Return True -> [ [] ]
If a t e -> map ((True,a):) (truePaths t) ++
map ((False,a):) (truePaths e)
-}
--------------------------------------------------------------------------------
-- Pretty print
ppAtom :: Atom -> Doc
ppAtom atom =
case atom of
AFin x -> text "fin" <+> ppName x
AGt x y -> ppExpr x <+> text ">" <+> ppExpr y
AEq x y -> ppExpr x <+> text "=" <+> ppExpr y
ppProp' :: I Bool -> Doc
ppProp' = ppIf ppAtom (text . show)
--------------------------------------------------------------------------------
-- General logic stuff
-- | False
pFalse :: I Bool
pFalse = Return False
-- | True
pTrue :: I Bool
pTrue = Return True
-- | Negation
pNot :: I Bool -> I Bool
pNot p =
case p of
Impossible -> Impossible
Return a -> Return (not a)
If c t e -> If c (pNot t) (pNot e)
-- | And
pAnd :: I Bool -> I Bool -> I Bool
pAnd p q = pIf p q pFalse
-- | Or
pOr :: I Bool -> I Bool -> I Bool
pOr p q = pIf p pTrue q
mkIf :: (Eq a, HasVars a) => Atom -> I a -> I a -> I a
mkIf a t e
| t == e = t
| otherwise = case a of
AFin x -> If a (pKnownFin x t) (pKnownInf x e)
_ | If b@(AFin y) _ _ <- t -> If b (mkFinIf y) (mkInfIf y)
| If b@(AFin y) _ _ <- e -> If b (mkFinIf y) (mkInfIf y)
AEq x' y'
| x == y -> t
| otherwise -> If (AEq x y) t e
where (x,y) = balanceEq x' y'
_ -> If a t e
where
mkFinIf y = mkIf a (pKnownFin y t) (pKnownFin y e)
mkInfIf y = case apSubstAtom (Map.singleton y (K Inf)) a of
Nothing -> mkIf a (pKnownInf y t) (pKnownInf y t)
Just a' -> pIf a' (pKnownInf y t) (pKnownInf y t)
-- | If-then-else with non-atom at decision.
pIf :: (Eq a, HasVars a) => I Bool -> I a -> I a -> I a
pIf c t e =
case c of
Impossible -> Impossible
Return True -> t
Return False -> e
If p t1 e1
| t2 == e2 -> t2
| otherwise -> mkIf p t2 e2
where
t2 = pIf t1 t e
e2 = pIf e1 t e
-- | Atoms to propositions.
pAtom :: Atom -> I Bool
pAtom p = do a <- case p of
AFin _ -> return p
AEq x y -> bin AEq x y
AGt x y -> bin AGt x y
If a pTrue pFalse
where
prep x = do y <- eNoInf x
case y of
K Inf -> Impossible
_ -> return (crySimpExpr y)
bin f x y = liftM2 f (prep x) (prep y)
--------------------------------------------------------------------------------
-- Implementation of Cryptol constraints
-- | Implementation of `==`
pEq :: Expr -> Expr -> I Bool
pEq x (K (Nat n)) = pIsNat n x
pEq (K (Nat n)) y = pIsNat n y
pEq x y = pIf (pInf x) (pInf y) (pAnd (pFin y) (pAtom (AEq x y)))
-- | Implementation of `>=`
pGeq :: Expr -> Expr -> I Bool
pGeq x y = pIf (pInf x) pTrue (pAnd (pFin y) (pAtom (AGt (one :+ x) y)))
-- | Implementation `e1 > e2`.
pGt :: Expr -> Expr -> I Bool
pGt x y = pNot (pGeq y x)
-- | Implementation of `Fin`
pFin :: Expr -> I Bool
pFin expr =
case expr of
K Inf -> pFalse
K (Nat _) -> pTrue
Var x -> pAtom (AFin x)
t1 :+ t2 -> pAnd (pFin t1) (pFin t2)
t1 :- _ -> pFin t1
t1 :* t2 -> pIf (pInf t1) (pEq t2 zero)
$ pIf (pInf t2) (pEq t1 zero)
$ pTrue
Div t1 _ -> pFin t1
Mod _ _ -> pTrue
t1 :^^ t2 -> pIf (pInf t1) (pEq t2 zero)
$ pIf (pInf t2) (pOr (pEq t1 zero) (pEq t1 one))
$ pTrue
Min t1 t2 -> pOr (pFin t1) (pFin t2)
Max t1 t2 -> pAnd (pFin t1) (pFin t2)
Width t1 -> pFin t1
LenFromThen _ _ _ -> pTrue
LenFromThenTo _ _ _ -> pTrue
-- | Implementation of `e == inf`
pInf :: Expr -> I Bool
pInf = pNot . pFin
pIsNat :: Integer -> Expr -> I Bool
pIsNat n expr =
case expr of
K Inf -> pFalse
K (Nat m) -> if m == n then pTrue else pFalse
Var _ -> nothing
K (Nat m) :+ e2 -> if n < m then pFalse
else pIsNat (n - m) e2
x :+ y
| n == 0 -> pAnd (pIsNat 0 x) (pIsNat 0 y)
| n == 1 -> pOr (pAnd (pIsNat 0 x) (pIsNat 1 y))
(pAnd (pIsNat 1 x) (pIsNat 0 y))
| otherwise -> nothing
e1 :- e2 -> pEq (K (Nat n) :+ e1) e2
K (Nat m) :* e2 ->
if m == 0
then if n == 0 then pTrue else pFalse
else case divMod n m of
(q,r) -> if r == 0 then pIsNat q e2
else pFalse
e1 :* e2
| n == 0 -> pOr (pIsNat 0 e1) (pIsNat 0 e2)
| n == 1 -> pAnd (pIsNat 1 e1) (pIsNat 1 e2)
| otherwise -> nothing
-- (x >= n * y) /\ ((n+1) * y > x)
Div x y -> pAnd (pGt (one :+ x) (K (Nat n) :* y))
(pGt (K (Nat (n + 1)) :* y) x)
Mod _ _ -> nothing
K (Nat m) :^^ y -> case genLog n m of
Just (a, exact) | exact -> pIsNat a y
_ -> pFalse
x :^^ K (Nat m) -> case rootExact n m of
Just a -> pIsNat a x
Nothing -> pFalse
x :^^ y
| n == 0 -> pAnd (pIsNat 0 x) (pGt y zero)
| n == 1 -> pOr (pIsNat 1 x) (pIsNat 0 y)
| otherwise -> nothing
Min x y
| n == 0 -> pOr (pIsNat 0 x) (pIsNat 0 y)
| otherwise -> pOr (pAnd (pIsNat n x) (pGt y (K (Nat (n - 1)))))
(pAnd (pIsNat n y) (pGt x (K (Nat (n - 1)))))
Max x y -> pOr (pAnd (pIsNat n x) (pGt (K (Nat (n + 1))) y))
(pAnd (pIsNat n y) (pGt (K (Nat (n + 1))) y))
Width x
| n == 0 -> pIsNat 0 x
| otherwise -> pAnd (pGt x (K (Nat (2^(n-1) - 1))))
(pGt (K (Nat (2 ^ n))) x)
x ->
panic "Cryptol.TypeCheck.Solver.Numeric.Simplify1.pIsNat"
[ "unexpected expression ", show x ]
{-
LenFromThen x y w
| n == 0 -> Just PFalse
-- See Note [Sequences of Length 1] in 'Cryptol.TypeCheck.Solver.InfNat'
| n == 1 -> Just (gt y x :&& gt (y :+ one) (two :^^ w))
| otherwise -> Nothing -- XXX: maybe some more?
-- See `nLenFromThenTo` in 'Cryptol.TypeCheck.Solver.InfNat'
LenFromThenTo x y z
| n == 0 -> Just ( gt x y :&& gt z x
:|| gt y x :&& gt x z
)
-- See Note [Sequences of Length 1] in 'Cryptol.TypeCheck.Solver.InfNat'
| n == 1 -> Just (gt z y :&& gt (x :+ one) z :||
gt y z :&& gt (z :+ one) x)
| otherwise -> Nothing -- XXX: maybe some more?
-}
where
nothing = pAnd (pFin expr) (pAtom (AEq expr (K (Nat n))))
_pIsGtThanNat :: Integer -> Expr -> I Bool
_pIsGtThanNat = undefined
_pNatIsGtThan :: Integer -> Expr -> I Bool
_pNatIsGtThan = undefined
--------------------------------------------------------------------------------
pKnownFin :: (HasVars a, Eq a) => Name -> I a -> I a
pKnownFin x prop =
case prop of
If (AFin y) t _
| x == y -> pKnownFin x t
If p t e -> mkIf p (pKnownFin x t) (pKnownFin x e)
_ -> prop
pKnownInf :: (Eq a, HasVars a) => Name -> I a -> I a
pKnownInf x prop = fromMaybe prop (apSubst (Map.singleton x (K Inf)) prop)
-- Cancel constants
-- If the original equation was valid, it continues to be valid.
balanceEq :: Expr -> Expr -> (Expr, Expr)
balanceEq (K (Nat a) :+ e1) (K (Nat b) :+ e2)
| a >= b = balanceEq e2 (K (Nat (a - b)) :+ e1)
| otherwise = balanceEq e1 (K (Nat (b - a)) :+ e2)
-- Move subtraction to the other side.
-- If the original equation was valid, this will continue to be valid.
balanceEq e1 e2
| not (null neg_es1 && null neg_es2) = balanceEq (mk neg_es2 pos_es1)
(mk neg_es1 pos_es2)
where
(pos_es1, neg_es1) = partitionEithers (map classify (splitSum e1))
(pos_es2, neg_es2) = partitionEithers (map classify (splitSum e2))
classify (sign,e) = case sign of
Pos -> Left e
Neg -> Right e
mk as bs = normSum (foldr (:+) zero (as ++ bs))
-- fallback
balanceEq x y = (x,y)
{- TODO: unused
balanceGt (K (Nat a) :+ e1) (K (Nat b) :+ e2)
| a >= b = balanceGt (K (Nat (a - b)) :+ e1) e2
| otherwise = balanceGt e1 (K (Nat (b - a)) :+ e2)
-}
--------------------------------------------------------------------------------
-- | Eliminate `inf`, except at the top level.
eNoInf :: Expr -> I Expr
eNoInf expr =
case expr of
-- These are the interesting cases where we have to branch
x :* y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(K Inf, K Inf) -> return inf
(K Inf, _) -> pIf (pEq y' zero) (return zero) (return inf)
(_, K Inf) -> pIf (pEq x' zero) (return zero) (return inf)
_ -> return (x' :* y')
x :^^ y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(K Inf, K Inf) -> return inf
(K Inf, _) -> pIf (pEq y' zero) (return one) (return inf)
(_, K Inf) -> pIf (pEq x' zero) (return zero)
$ pIf (pEq x' one) (return one)
$ return inf
_ -> return (x' :^^ y')
-- The rest just propagates
K _ -> return expr
Var _ -> return expr
x :+ y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(K Inf, _) -> return inf
(_, K Inf) -> return inf
_ -> return (x' :+ y')
x :- y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(_, K Inf) -> Impossible
(K Inf, _) -> return inf
_ -> return (x' :- y')
Div x y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(K Inf, _) -> Impossible
(_, K Inf) -> return zero
_ -> return (Div x' y')
Mod x y ->
do x' <- eNoInf x
-- `Mod x y` is finite, even if `y` is `inf`, so first check
-- for finiteness.
pIf (pFin y)
(do y' <- eNoInf y
case (x',y') of
(K Inf, _) -> Impossible
(_, K Inf) -> Impossible
_ -> return (Mod x' y')
)
(return x')
Min x y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x',y') of
(K Inf, _) -> return y'
(_, K Inf) -> return x'
_ -> return (Min x' y')
Max x y ->
do x' <- eNoInf x
y' <- eNoInf y
case (x', y') of
(K Inf, _) -> return inf
(_, K Inf) -> return inf
_ -> return (Max x' y')
Width x ->
do x' <- eNoInf x
case x' of
K Inf -> return inf
_ -> return (Width x')
LenFromThen x y w -> fun3 LenFromThen x y w
LenFromThenTo x y z -> fun3 LenFromThenTo x y z
where
fun3 f x y z =
do x' <- eNoInf x
y' <- eNoInf y
z' <- eNoInf z
case (x',y',z') of
(K Inf, _, _) -> Impossible
(_, K Inf, _) -> Impossible
(_, _, K Inf) -> Impossible
_ -> return (f x' y' z')
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/SimplifyExpr.hs 0000644 0000000 0000000 00000013711 12737220176 023356 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Simplification of expressions.
-- The result of simplifying an expression `e`, is a new expression `e'`,
-- which satisfies the property:
--
-- if e is well-defined then e and e' will evaluate to the same type.
--
{-# LANGUAGE Safe, BangPatterns #-}
module Cryptol.TypeCheck.Solver.Numeric.SimplifyExpr where
import Cryptol.TypeCheck.Solver.Numeric.AST
import qualified Cryptol.TypeCheck.Solver.InfNat as IN
import Cryptol.Utils.Misc ( anyJust )
import Control.Monad ( guard )
import Data.Maybe ( fromMaybe, maybeToList )
import qualified Data.Map as Map
-- | Simplify an expression, if possible.
crySimpExpr :: Expr -> Expr
crySimpExpr expr = fromMaybe expr (crySimpExprMaybe expr)
-- | Perform simplification from the leaves up.
-- Returns `Nothing` if there were no changes.
crySimpExprMaybe :: Expr -> Maybe Expr
crySimpExprMaybe expr =
case crySimpExprStep (fromMaybe expr mbE1) of
Nothing -> mbE1
Just e2 -> Just (fromMaybe e2 (crySimpExprMaybe e2))
where
mbE1 = cryRebuildExpr expr `fmap` anyJust crySimpExprMaybe (cryExprExprs expr)
-- XXX: Add rules to group together occurances of variables
data Sign = Pos | Neg deriving Show
otherSign :: Sign -> Sign
otherSign s = case s of
Pos -> Neg
Neg -> Pos
signed :: Sign -> Integer -> Integer
signed s = case s of
Pos -> id
Neg -> negate
splitSum :: Expr -> [(Sign,Expr)]
splitSum e0 = go Pos e0 []
where go s (e1 :+ e2) es = go s e1 (go s e2 es)
go s (e1 :- e2) es = go s e1 (go (otherSign s) e2 es)
go s e es = (s,e) : es
normSum :: Expr -> Expr
normSum = posTerm . go 0 Map.empty Nothing . splitSum
where
-- constants, variables, other terms
go !_ !_ !_ ((Pos,K Inf) : _) = (Pos, K Inf)
go k xs t ((s, K (Nat n)) : es) = go (k + signed s n) xs t es
go k xs t ((s, Var x) : es) = go k (Map.insertWith (+) x (signed s 1) xs) t es
go k xs t ((s, K (Nat n) :* Var x) : es)
| n == 0 = go k xs t es
| otherwise = go k (Map.insertWith (+) x (signed s n) xs) t es
go k xs Nothing (e : es) = go k xs (Just e) es
go k xs (Just e1) (e2 : es) = go k xs (Just (add e1 e2)) es
go k xs t [] =
let terms = constTerm k
++ concatMap varTerm (Map.toList xs)
++ maybeToList t
in case terms of
[] -> (Pos, K (Nat 0))
ts -> foldr1 add ts
constTerm k
| k == 0 = []
| k > 0 = [ (Pos, K (Nat k)) ]
| otherwise = [ (Neg, K (Nat (negate k))) ]
varTerm (x,k)
| k == 0 = []
| k == 1 = [ (Pos, Var x) ]
| k > 0 = [ (Pos, K (Nat k) :* Var x) ]
| k == (-1) = [ (Neg, Var x) ]
| otherwise = [ (Neg, K (Nat (negate k)) :* Var x) ]
add (s1,t1) (s2,t2) =
case (s1,s2) of
(Pos,Pos) -> (Pos, t1 :+ t2)
(Pos,Neg) -> (Pos, t1 :- t2)
(Neg,Pos) -> (Pos, t2 :- t1)
(Neg,Neg) -> (Neg, t1 :+ t2)
posTerm (Pos,x) = x
posTerm (Neg,x) = K (Nat 0) :- x
crySimpExprStep :: Expr -> Maybe Expr
crySimpExprStep e =
case crySimpExprStep1 e of
Just e1 -> Just e1
Nothing -> do let e1 = normSum e
guard (e /= e1)
return e1
-- | Make a simplification step, assuming the expression is well-formed.
crySimpExprStep1 :: Expr -> Maybe Expr
crySimpExprStep1 expr =
case expr of
K _ -> Nothing
Var _ -> Nothing
_ :+ _ -> Nothing
_ :- _ -> Nothing
x :* y ->
case (x,y) of
(K (Nat 0), _) -> Just zero
(K (Nat 1), _) -> Just y
(K a, K b) -> Just (K (IN.nMul a b))
(_, K _) -> Just (y :* x)
(K a, K b :* z) -> Just (K (IN.nMul a b) :* z)
-- Normalize, somewhat
(a :* b, _) -> Just (a :* (b :* y))
(Var a, Var b)
| b > a -> Just (y :* x)
_ -> Nothing
Div x y ->
case (x,y) of
(K (Nat 0), _) -> Just zero
(_, K (Nat 1)) -> Just x
(_, K Inf) -> Just zero
(K a, K b) -> K `fmap` IN.nDiv a b
_ | x == y -> Just one
_ -> Nothing
Mod x y ->
case (x,y) of
(K (Nat 0), _) -> Just zero
(_, K Inf) -> Just x
(_, K (Nat 1)) -> Just zero
(K a, K b) -> K `fmap` IN.nMod a b
_ -> Nothing
x :^^ y ->
case (x,y) of
(_, K (Nat 0)) -> Just one
(_, K (Nat 1)) -> Just x
(K (Nat 1), _) -> Just one
(K a, K b) -> Just (K (IN.nExp a b))
_ -> Nothing
Min x y ->
case (x,y) of
(K (Nat 0), _) -> Just zero
(K Inf, _) -> Just y
(_, K (Nat 0)) -> Just zero
(_, K Inf) -> Just x
(K a, K b) -> Just (K (IN.nMin a b))
_ | x == y -> Just x
_ -> Nothing
Max x y ->
case (x,y) of
(K (Nat 0), _) -> Just y
(K Inf, _) -> Just inf
(_, K (Nat 0)) -> Just x
(_, K Inf) -> Just inf
(K a, K b) -> Just (K (IN.nMax a b))
_ | x == y -> Just x
_ -> Nothing
Width x ->
case x of
K a -> Just (K (IN.nWidth a))
K (Nat 2) :^^ e -> Just (one :+ e)
K (Nat 2) :^^ e :- K (Nat 1) -> Just e
_ -> Nothing
LenFromThen x y w ->
case (x,y,w) of
(K a, K b, K c) -> K `fmap` IN.nLenFromThen a b c
_ -> Nothing
LenFromThenTo x y z ->
case (x,y,z) of
(K a, K b, K c) -> K `fmap` IN.nLenFromThenTo a b c
_ -> Nothing
cryptol-2.4.0/src/Cryptol/TypeCheck/Solver/Numeric/SMT.hs 0000644 0000000 0000000 00000041437 12737220176 021374 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
--
-- Desugar into SMTLIB Terminology
{-# LANGUAGE Safe #-}
module Cryptol.TypeCheck.Solver.Numeric.SMT
( desugarProp
, smtName
, smtFinName
, ifPropToSmtLib
, cryImproveModel
, getVal
, getVals
) where
import Cryptol.TypeCheck.AST (TVar(TVFree,TVBound))
import Cryptol.TypeCheck.Solver.InfNat
import Cryptol.TypeCheck.Solver.Numeric.AST
import Cryptol.TypeCheck.Solver.Numeric.Simplify(crySimplify)
import Cryptol.Utils.Misc ( anyJust )
import Cryptol.Utils.Panic ( panic )
import Data.List ( partition, unfoldr )
import Data.Map ( Map )
import qualified Data.Map as Map
import qualified Data.Set as Set
import SimpleSMT ( SExpr )
import qualified SimpleSMT as SMT
import MonadLib
--------------------------------------------------------------------------------
-- Desugar to SMT
--------------------------------------------------------------------------------
-- XXX: Expanding the if-then-elses could make things large.
-- Perhaps keep them as first class things, in hope that the solver
-- can do something more clever with that?
-- | Assumes simplified, linear, finite, defined expressions.
desugarExpr :: Expr -> IfExpr Expr
desugarExpr expr =
do es <- mapM desugarExpr (cryExprExprs expr)
case (expr,es) of
(Min {}, [x,y]) -> If (x :>: y) (return y) (return x)
(Max {}, [x,y]) -> If (x :>: y) (return x) (return y)
(LenFromThenTo {}, [ x@(K (Nat a)), K (Nat b), z ])
-- going down
| a > b -> If (z :>: x) (return zero)
(return (Div (x :- z) step :+ one))
-- goind up
| b > a -> If (x :>: z) (return zero)
(return (Div (z :- x) step :+ one))
where step = K (Nat (abs (a - b)))
_ -> return (cryRebuildExpr expr es)
-- | Assumes simplified, linear, defined.
desugarProp :: Prop -> IfExpr Prop
desugarProp prop =
case prop of
PFalse -> return PFalse
PTrue -> return PTrue
Not p -> Not `fmap` desugarProp p
p :&& q -> (:&&) `fmap` desugarProp p `ap` desugarProp q
p :|| q -> (:||) `fmap` desugarProp p `ap` desugarProp q
Fin (Var _) -> return prop
x :==: y -> (:==:) `fmap` desugarExpr x `ap` desugarExpr y
x :>: y -> (:>:) `fmap` desugarExpr x `ap` desugarExpr y
Fin _ -> unexpected
_ :== _ -> unexpected
_ :>= _ -> unexpected
_ :> _ -> unexpected
where
unexpected = panic "desugarProp" [ show (ppProp prop) ]
ifPropToSmtLib :: IfExpr Prop -> SExpr
ifPropToSmtLib ifProp =
case ifProp of
Impossible -> SMT.bool False -- Sholdn't really matter
Return p -> propToSmtLib p
If p q r -> SMT.ite (propToSmtLib p) (ifPropToSmtLib q) (ifPropToSmtLib r)
propToSmtLib :: Prop -> SExpr
propToSmtLib prop =
case prop of
PFalse -> SMT.bool False
PTrue -> SMT.bool True
Not p -> case p of
Fin _ -> SMT.not (propToSmtLib p)
-- It is IMPORTANT that the fin constraints are outside
-- the not.
x :>: y -> addFin $ SMT.geq (exprToSmtLib y)
(exprToSmtLib x)
_ -> unexpected
p :&& q -> SMT.and (propToSmtLib p) (propToSmtLib q)
p :|| q -> SMT.or (propToSmtLib p) (propToSmtLib q)
Fin (Var x) -> fin x
{- For the linear constraints, if the term is finite, then all of
its variables must have been finite.
XXX: Adding the `fin` decls at the leaves leads to some duplication:
We could add them just once for each conjunctoin of simple formulas,
but I am not sure how much this matters.
-}
x :==: y -> addFin $ SMT.eq (exprToSmtLib x) (exprToSmtLib y)
x :>: y -> addFin $ SMT.gt (exprToSmtLib x) (exprToSmtLib y)
Fin _ -> unexpected
_ :== _ -> unexpected
_ :>= _ -> unexpected
_ :> _ -> unexpected
where
unexpected = panic "propToSmtLib" [ show (ppProp prop) ]
fin x = SMT.const (smtFinName x)
addFin e = foldr (\x' e' -> SMT.and (fin x') e') e
(Set.toList (cryPropFVS prop))
exprToSmtLib :: Expr -> SExpr
exprToSmtLib expr =
case expr of
K (Nat n) -> SMT.int n
Var a -> SMT.const (smtName a)
x :+ y -> SMT.add (exprToSmtLib x) (exprToSmtLib y)
x :- y -> SMT.sub (exprToSmtLib x) (exprToSmtLib y)
x :* y -> SMT.mul (exprToSmtLib x) (exprToSmtLib y)
Div x y -> SMT.div (exprToSmtLib x) (exprToSmtLib y)
Mod x y -> SMT.mod (exprToSmtLib x) (exprToSmtLib y)
K Inf -> unexpected
_ :^^ _ -> unexpected
Min {} -> unexpected
Max {} -> unexpected
Width {} -> unexpected
LenFromThen {} -> unexpected
LenFromThenTo {} -> unexpected
where
unexpected = panic "exprToSmtLib" [ show (ppExpr expr) ]
-- | The name of a variable in the SMT translation.
smtName :: Name -> String
smtName a = case a of
SysName n -> name "s" n
UserName tv -> case tv of
TVFree n _ _ _ -> name "u" n
TVBound n _ -> name "k" n
where
name p n = case divMod n 26 of
(q,r) -> p ++ toEnum (fromEnum 'a' + r) :
(if q == 0 then "" else show q)
-- | The name of a boolean variable, representing `fin x`.
smtFinName :: Name -> String
smtFinName x = "fin_" ++ smtName x
--------------------------------------------------------------------------------
-- Models
--------------------------------------------------------------------------------
{- | Get the value for the given name.
* Assumes that we are in a SAT state (i.e., there is a model)
* Assumes that the name is in the model -}
getVal :: SMT.Solver -> Name -> IO Nat'
getVal s a =
do yes <- isInf a
if yes
then return Inf
else do v <- SMT.getConst s (smtName a)
case v of
SMT.Int x | x >= 0 -> return (Nat x)
_ -> panic "cryCheck.getVal" [ "Not a natural number", show v ]
where
isInf v = do yes <- SMT.getConst s (smtFinName v)
case yes of
SMT.Bool ans -> return (not ans)
_ -> panic "cryCheck.isInf"
[ "Not a boolean value", show yes ]
-- | Get the values for the given names.
getVals :: SMT.Solver -> [Name] -> IO (Map Name Nat')
getVals s xs =
do es <- mapM (getVal s) xs
return (Map.fromList (zip xs es))
-- | Convert a bunch of improving equations into an idempotent substitution.
-- Assumes that the equations don't have loops.
toSubst :: Map Name Expr -> Subst
toSubst m0 = last (m0 : unfoldr step m0)
where step m = do m1 <- anyJust (apSubst m) m
return (m1,m1)
{- | Given a model, compute an improving substitution, implied by the model.
The entries in the substitution look like this:
* @x = A@ variable @x@ must equal constant @A@
* @x = y@ variable @x@ must equal variable @y@
* @x = A * y + B@ (coming soon)
variable @x@ is a linear function of @y@,
@A@ and @B@ are natural numbers.
-}
{- | We are mostly interested in improving unification variables.
However, it is also useful to improve skolem variables, as this could
turn non-linear constraints into linear ones. For example, if we
have a constraint @x * y = z@, and we can figure out that @x@ must be 5,
then we end up with a linear constraint @5 * y = z@.
-}
cryImproveModel :: SMT.Solver -> SMT.Logger -> Map Name Nat'
-> IO (Map Name Expr, [Prop])
cryImproveModel solver logger model =
do (imps,subGoals) <- go Map.empty [] initialTodo
return (toSubst imps, subGoals)
where
-- Process unification variables first. That way, if we get `x = y`, we'd
-- prefer `x` to be a unification variable.
initialTodo = uncurry (++) $ partition (isUniVar . fst) $ Map.toList model
isUniVar x = case x of
UserName (TVFree {}) -> True
_ -> False
-- done: the set of known improvements
-- extra: the collection of inferred sub-goals
go done extra [] = return (done,extra)
go done extra ((x,e) : rest) =
-- x = K?
do mbCounter <- cryMustEqualK solver (Map.keys model) x e
case mbCounter of
Nothing -> go (Map.insert x (K e) done) extra rest
Just ce -> goV ce done extra [] x e rest
-- ce: a counter example to `x = e`
-- done: known improvements
-- extra: known sub-goals
-- todo: more work to process once we are done with `x`.
goV _ done extra todo _ _ [] = go done extra (reverse todo)
goV ce done extra todo x e ((y,e') : more)
-- x = y?
| e == e' = do yesK <- cryMustEqualV solver x y
if yesK then go (Map.insert x (Var y) done)
extra
(reverse todo ++ more)
else tryLR
| otherwise = tryLR
where
next = goV ce done extra ((y,e'):todo) x e more
tryLR =
do mb <- tryLR_with x e y e'
case mb of
Just (r,subGoals) -> go (Map.insert x r done)
(subGoals ++ extra)
(reverse todo ++ more)
Nothing ->
do mb1 <- tryLR_with y e' x e
case mb1 of
Nothing -> next
Just (r, subGoals) -> go (Map.insert y r done)
(subGoals ++ extra)
(reverse todo ++ more)
tryLR_with v1 v1Expr v2 v2Expr =
case ( isUniVar v1
, v1Expr
, v2Expr
, Map.lookup v1 ce
, Map.lookup v2 ce
) of
(True, x1, y1, Just x2, Just y2) ->
cryCheckLinRel solver logger v2 v1 (y1,x1) (y2,x2)
_ -> return Nothing
-- | Try to prove the given expression.
checkUnsat :: SMT.Solver -> SExpr -> IO Bool
checkUnsat s e =
do SMT.push s
SMT.assert s e
res <- SMT.check s
SMT.pop s
return (res == SMT.Unsat)
-- | Try to prove the given expression.
-- If we fail, we try to give a counter example.
-- If the answer is unknown, then we return an empty counter example.
getCounterExample :: SMT.Solver -> [Name] -> SExpr -> IO (Maybe (Map Name Nat'))
getCounterExample s xs e =
do SMT.push s
SMT.assert s e
res <- SMT.check s
ans <- case res of
SMT.Unsat -> return Nothing
SMT.Unknown -> return (Just Map.empty)
SMT.Sat -> Just `fmap` getVals s xs
SMT.pop s
return ans
-- | Is this the only possible value for the constant, under the current
-- assumptions.
-- Assumes that we are in a 'Sat' state.
-- Returns 'Nothing' if the variables must always match the given value.
-- Otherwise, we return a counter-example (which may be empty, if uniknown)
cryMustEqualK :: SMT.Solver -> [Name] ->
Name -> Nat' -> IO (Maybe (Map Name Nat'))
cryMustEqualK solver xs x val =
case val of
Inf -> getCounterExample solver xs (SMT.const (smtFinName x))
Nat n -> getCounterExample solver xs $
SMT.not $
SMT.and (SMT.const $ smtFinName x)
(SMT.eq (SMT.const (smtName x)) (SMT.int n))
-- | Do these two variables need to always be the same, under the current
-- assumptions.
-- Assumes that we are in a 'Sat' state.
cryMustEqualV :: SMT.Solver -> Name -> Name -> IO Bool
cryMustEqualV solver x y =
checkUnsat solver $
SMT.not $
SMT.or (SMT.not (fin x) `SMT.and` SMT.not (fin y))
(fin x `SMT.and` fin y `SMT.and` SMT.eq (var x) (var y))
where fin a = SMT.const (smtFinName a)
var a = SMT.const (smtName a)
-- | Try to find a linear relation between the two variables, based
-- on two observed data points.
-- NOTE: The variable being defined is the SECOND name.
cryCheckLinRel :: SMT.Solver -> SMT.Logger ->
{- x -} Name {- ^ Definition in terms of this variable. -} ->
{- y -} Name {- ^ Define this variable. -} ->
(Nat',Nat') {- ^ Values in one model (x,y) -} ->
(Nat',Nat') {- ^ Values in another model (x,y) -} ->
IO (Maybe (Expr,[Prop]))
{- ^ Either nothing, or an improving expression, and any
additional obligations -}
cryCheckLinRel s logger x y p1 p2 =
-- First, try to find a linear relation that holds in all finite cases.
do SMT.push s
SMT.assert s (isFin x)
SMT.assert s (isFin y)
ans <- case (p1,p2) of
((Nat x1, Nat y1), (Nat x2, Nat y2)) ->
checkLR x1 y1 x2 y2
((Inf, Inf), (Nat x2, Nat y2)) ->
mbGoOn (getFinPt x2) $ \(x1,y1) -> checkLR x1 y1 x2 y2
((Nat x1, Nat y1), (Inf, Inf)) ->
mbGoOn (getFinPt x1) $ \(x2,y2) -> checkLR x1 y1 x2 y2
_ -> return Nothing
SMT.pop s
-- Next, check the infinite cases: if @y = A * x + B@, then
-- either both @x@ and @y@ must be infinite or they both must be finite.
-- Note that we don't consider relations where A = 0: because they
-- would be handled when we checked that @y@ is a constant.
case ans of
Nothing -> return Nothing
Just e ->
do SMT.push s
SMT.assert s (SMT.not (SMT.eq (isFin x) (isFin y)))
c <- SMT.check s
SMT.pop s
case c of
SMT.Unsat -> return (Just e)
_ -> return Nothing
where
isFin a = SMT.const (smtFinName a)
-- XXX: Duplicates `cryDefined`
-- The constraints are always of the form: x >= K, or K >= x
wellDefined e =
case e of
(K (Nat a) :* t) :- K (Nat b) ->
let c = div (b + a - 1) a
in [ t :>= K (Nat c) ]
K (Nat b) :- (K (Nat a) :* t)
-> let c = div b a
in [ K (Nat c) :>= t ]
a :- b -> [ a :>= b ]
_ -> []
checkLR x1 y1 x2 y2 =
do SMT.logMessage logger ("checkLR: " ++ show (x1,y1) ++ " "
++ show (x2,y2))
mbGoOn (return (linRel (x1,y1) (x2,y2))) (\(a,b) ->
do let sumTerm v
| b == 0 = v
| b < 0 = v :- K (Nat (negate b))
| otherwise = v :+ K (Nat b)
expr
| a == 1 = sumTerm (Var x)
| a < 0 = K (Nat b) :- K (Nat (negate a)) :* Var x
| otherwise = sumTerm (K (Nat a) :* Var x)
SMT.logMessage logger ("candidate: " ++ show (ppProp (Var y :==: expr)))
proved <- checkUnsat s
$ propToSmtLib $ crySimplify
$ Not $ Var y :==: expr
if not proved
then SMT.logMessage logger "failed" >> return Nothing
else return (Just (expr,wellDefined expr)))
-- Try to get an example of another point, which is finite, and at
-- different @x@ coordinate.
getFinPt otherX =
do SMT.push s
SMT.assert s (SMT.not (SMT.eq (SMT.const (smtName x)) (SMT.int otherX)))
smtAns <- SMT.check s
ans <- case smtAns of
SMT.Sat ->
do vX <- SMT.getConst s (smtName x)
vY <- SMT.getConst s (smtName y)
case (vX, vY) of
(SMT.Int vx, SMT.Int vy)
| vx >= 0 && vy >= 0 -> return (Just (vx,vy))
_ -> return Nothing
_ -> return Nothing
SMT.pop s
return ans
mbGoOn m k = do ans <- m
case ans of
Nothing -> return Nothing
Just a -> k a
{- | Compute a linear relation through two concrete points.
Try to find a relation of the form @y = a * x + b@.
Depending on the signs of @a@ and @b@, we need additional checks,
to ensure tha @a * x + b@ is valid.
y1 = A * x1 + B
y2 = A * x2 + B
(y2 - y1) = A * (x2 - x1)
A = (y2 - y1) / (x2 - x1)
B = y1 - A * x1
-}
linRel :: (Integer,Integer) {- ^ First point -} ->
(Integer,Integer) {- ^ Second point -} ->
Maybe (Integer,Integer) {- ^ (A,B) -}
linRel (x1,y1) (x2,y2) =
do guard (x1 /= x2)
let (a,r) = divMod (y2 - y1) (x2 - x1)
guard (r == 0 && a /= 0) -- Not interested in A = 0
let b = y1 - a * x1
guard $ not $ a < 0 && b < 0 -- No way this will give a natural number.
return (a,b)
cryptol-2.4.0/src/Cryptol/Utils/ 0000755 0000000 0000000 00000000000 12737220176 014731 5 ustar 00 0000000 0000000 cryptol-2.4.0/src/Cryptol/Utils/Debug.hs 0000644 0000000 0000000 00000000577 12737220176 016324 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
module Cryptol.Utils.Debug where
import Cryptol.Utils.PP
import qualified Debug.Trace as X
trace :: String -> b -> b
trace = X.trace
ppTrace :: Doc -> b -> b
ppTrace d = trace (show d)
cryptol-2.4.0/src/Cryptol/Utils/Ident.hs 0000644 0000000 0000000 00000004332 12737220176 016332 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2015-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE DeriveGeneric #-}
module Cryptol.Utils.Ident where
import Control.DeepSeq (NFData)
import Data.Char (isSpace)
import Data.List (unfoldr)
import qualified Data.Text as T
import Data.String (IsString(..))
import GHC.Generics (Generic)
-- | Module names are just text.
type ModName = T.Text
unpackModName :: ModName -> [String]
unpackModName = unfoldr step
where
step str
| T.null str = Nothing
| otherwise = case T.breakOn modSep str of
(a,b) -> Just (T.unpack a,T.drop (T.length modSep) b)
packModName :: [String] -> ModName
packModName strs = T.intercalate modSep (map (trim . T.pack) strs)
where
-- trim space off of the start and end of the string
trim str = T.dropWhile isSpace (T.dropWhileEnd isSpace str)
modSep :: T.Text
modSep = T.pack "::"
-- | Identifiers, along with a flag that indicates whether or not they're infix
-- operators. The boolean is present just as cached information from the lexer,
-- and never used during comparisons.
data Ident = Ident Bool T.Text
deriving (Show,Generic)
instance Eq Ident where
a == b = compare a b == EQ
a /= b = compare a b /= EQ
instance Ord Ident where
compare (Ident _ i1) (Ident _ i2) = compare i1 i2
instance IsString Ident where
fromString str = mkIdent (T.pack str)
instance NFData Ident
packIdent :: String -> Ident
packIdent = mkIdent . T.pack
packInfix :: String -> Ident
packInfix = mkInfix . T.pack
unpackIdent :: Ident -> String
unpackIdent = T.unpack . identText
mkIdent :: T.Text -> Ident
mkIdent = Ident False
mkInfix :: T.Text -> Ident
mkInfix = Ident True
isInfixIdent :: Ident -> Bool
isInfixIdent (Ident b _) = b
nullIdent :: Ident -> Bool
nullIdent (Ident _ t) = T.null t
identText :: Ident -> T.Text
identText (Ident _ t) = t
-- Frequently Used Names -------------------------------------------------------
preludeName :: ModName
preludeName = packModName ["Cryptol"]
interactiveName :: ModName
interactiveName = packModName [""]
cryptol-2.4.0/src/Cryptol/Utils/Misc.hs 0000644 0000000 0000000 00000002106 12737220176 016157 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2014-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe, FlexibleContexts #-}
module Cryptol.Utils.Misc where
import MonadLib
import Data.Maybe(fromMaybe)
import Prelude ()
import Prelude.Compat
-- | Apply a function to all elements of a container.
-- Returns `Nothing` if nothing changed, and @Just container@ otherwise.
anyJust :: Traversable t => (a -> Maybe a) -> t a -> Maybe (t a)
anyJust f m = mk $ runId $ runStateT False $ traverse upd m
where
mk (a,changes) = if changes then Just a else Nothing
upd x = case f x of
Just y -> set True >> return y
Nothing -> return x
-- | Apply functions to both elements of a pair.
-- Returns `Nothing` if neither changed, and @Just pair@ otherwise.
anyJust2 :: (a -> Maybe a) -> (b -> Maybe b) -> (a,b) -> Maybe (a,b)
anyJust2 f g (a,b) =
case (f a, g b) of
(Nothing, Nothing) -> Nothing
(x,y) -> Just (fromMaybe a x, fromMaybe b y)
cryptol-2.4.0/src/Cryptol/Utils/Panic.hs 0000644 0000000 0000000 00000003210 12737220176 016313 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveDataTypeable, RecordWildCards #-}
module Cryptol.Utils.Panic (panic) where
import Cryptol.Version
import Control.Exception as X
import Data.Typeable(Typeable)
import Data.Maybe(fromMaybe,listToMaybe)
panic :: String -> [String] -> a
panic panicLoc panicMsg = throw CryptolPanic { .. }
data CryptolPanic = CryptolPanic { panicLoc :: String
, panicMsg :: [String]
} deriving Typeable
instance Show CryptolPanic where
show p = unlines $
[ "You have encountered a bug in Cryptol's implementation."
, "*** Please create an issue at https://github.com/galoisinc/cryptol/issues"
, ""
, "%< --------------------------------------------------- "
] ++ rev ++
[ locLab ++ panicLoc p
, msgLab ++ fromMaybe "" (listToMaybe msgLines)
]
++ map (tabs ++) (drop 1 msgLines) ++
[ "%< --------------------------------------------------- "
]
where msgLab = " Message: "
revLab = " Revision: "
branchLab = " Branch: "
dirtyLab = " (non-committed files present during build)"
locLab = " Location: "
tabs = map (const ' ') msgLab
msgLines = panicMsg p
rev | null commitHash = []
| otherwise = [ revLab ++ commitHash
, branchLab ++ commitBranch ++ dirtyLab ]
instance Exception CryptolPanic
cryptol-2.4.0/src/Cryptol/Utils/PP.hs 0000644 0000000 0000000 00000016216 12737220176 015612 0 ustar 00 0000000 0000000 -- |
-- Module : $Header$
-- Copyright : (c) 2013-2016 Galois, Inc.
-- License : BSD3
-- Maintainer : cryptol@galois.com
-- Stability : provisional
-- Portability : portable
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternGuards #-}
module Cryptol.Utils.PP where
import Cryptol.Utils.Ident
import Control.DeepSeq
import Control.Monad (mplus)
import Data.Maybe (fromMaybe)
import Data.String (IsString(..))
import qualified Data.Text as T
import GHC.Generics (Generic)
import qualified Text.PrettyPrint as PJ
import Prelude ()
import Prelude.Compat
-- Name Displaying -------------------------------------------------------------
-- | How to display names, inspired by the GHC `Outputable` module. Getting a
-- value of 'Nothing' from the NameDisp function indicates that the name is not
-- in scope.
data NameDisp = EmptyNameDisp
| NameDisp (ModName -> Ident -> Maybe NameFormat)
deriving (Generic, NFData)
instance Show NameDisp where
show _ = ""
instance Monoid NameDisp where
mempty = EmptyNameDisp
mappend (NameDisp f) (NameDisp g) = NameDisp (\m n -> f m n `mplus` g m n)
mappend EmptyNameDisp EmptyNameDisp = EmptyNameDisp
mappend EmptyNameDisp x = x
mappend x _ = x
data NameFormat = UnQualified
| Qualified !ModName
| NotInScope
deriving (Show)
-- | Never qualify names from this module.
neverQualifyMod :: ModName -> NameDisp
neverQualifyMod mn = NameDisp $ \ mn' _ ->
if mn == mn' then Just UnQualified
else Nothing
alwaysQualify :: NameDisp
alwaysQualify = NameDisp $ \ mn _ -> Just (Qualified mn)
neverQualify :: NameDisp
neverQualify = NameDisp $ \ _ _ -> Just UnQualified
fmtModName :: ModName -> NameFormat -> ModName
fmtModName _ UnQualified = T.empty
fmtModName _ (Qualified mn) = mn
fmtModName mn NotInScope = mn
-- | Compose two naming environments, preferring names from the left
-- environment.
extend :: NameDisp -> NameDisp -> NameDisp
extend = mappend
-- | Get the format for a name. When 'Nothing' is returned, the name is not
-- currently in scope.
getNameFormat :: ModName -> Ident -> NameDisp -> NameFormat
getNameFormat m i (NameDisp f) = fromMaybe NotInScope (f m i)
getNameFormat _ _ EmptyNameDisp = NotInScope
-- | Produce a document in the context of the current 'NameDisp'.
withNameDisp :: (NameDisp -> Doc) -> Doc
withNameDisp k = Doc (\disp -> runDoc disp (k disp))
-- | Fix the way that names are displayed inside of a doc.
fixNameDisp :: NameDisp -> Doc -> Doc
fixNameDisp disp (Doc f) = Doc (\ _ -> f disp)
-- Documents -------------------------------------------------------------------
newtype Doc = Doc (NameDisp -> PJ.Doc) deriving (Generic, NFData)
instance Monoid Doc where
mempty = liftPJ PJ.empty
mappend = liftPJ2 (PJ.<>)
runDoc :: NameDisp -> Doc -> PJ.Doc
runDoc names (Doc f) = f names
instance Show Doc where
show d = show (runDoc mempty d)
instance IsString Doc where
fromString = text
render :: Doc -> String
render d = PJ.render (runDoc mempty d)
class PP a where
ppPrec :: Int -> a -> Doc
class PP a => PPName a where
-- | Fixity information for infix operators
ppNameFixity :: a -> Maybe (Assoc, Int)
-- | Print a name in prefix: @f a b@ or @(+) a b)@
ppPrefixName :: a -> Doc
-- | Print a name as an infix operator: @a + b@
ppInfixName :: a -> Doc
pp :: PP a => a -> Doc
pp = ppPrec 0
pretty :: PP a => a -> String
pretty = show . pp
optParens :: Bool -> Doc -> Doc
optParens b body | b = parens body
| otherwise = body
-- | Information about associativity.
data Assoc = LeftAssoc | RightAssoc | NonAssoc
deriving (Show, Eq, Generic, NFData)
-- | Information about an infix expression of some sort.
data Infix op thing = Infix
{ ieOp :: op -- ^ operator
, ieLeft :: thing -- ^ left argument
, ieRight :: thing -- ^ right argumrnt
, iePrec :: Int -- ^ operator precedence
, ieAssoc :: Assoc -- ^ operator associativity
}
commaSep :: [Doc] -> Doc
commaSep = fsep . punctuate comma
-- | Pretty print an infix expression of some sort.
ppInfix :: (PP thing, PP op)
=> Int -- ^ Non-infix leaves are printed with this precedence
-> (thing -> Maybe (Infix op thing))
-- ^ pattern to check if sub-thing is also infix
-> Infix op thing -- ^ Pretty print this infix expression
-> Doc
ppInfix lp isInfix expr =
sep [ ppSub (wrapSub LeftAssoc ) (ieLeft expr) <+> pp (ieOp expr)
, ppSub (wrapSub RightAssoc) (ieRight expr) ]
where
wrapSub dir p = p < iePrec expr || p == iePrec expr && ieAssoc expr /= dir
ppSub w e
| Just e1 <- isInfix e = optParens (w (iePrec e1)) (ppInfix lp isInfix e1)
ppSub _ e = ppPrec lp e
-- | Display a numeric values as an ordinar (e.g., 2nd)
ordinal :: (Integral a, Show a, Eq a) => a -> Doc
ordinal x = text (show x) <> text (ordSuffix x)
-- | The suffix to use when displaying a number as an oridinal
ordSuffix :: (Integral a, Eq a) => a -> String
ordSuffix n0 =
case n `mod` 10 of
1 | notTeen -> "st"
2 | notTeen -> "nd"
3 | notTeen -> "rd"
_ -> "th"
where
n = abs n0
m = n `mod` 100
notTeen = m < 11 || m > 19
-- Wrapped Combinators ---------------------------------------------------------
liftPJ :: PJ.Doc -> Doc
liftPJ d = Doc (const d)
liftPJ1 :: (PJ.Doc -> PJ.Doc) -> Doc -> Doc
liftPJ1 f (Doc d) = Doc (\env -> f (d env))
liftPJ2 :: (PJ.Doc -> PJ.Doc -> PJ.Doc) -> (Doc -> Doc -> Doc)
liftPJ2 f (Doc a) (Doc b) = Doc (\e -> f (a e) (b e))
liftSep :: ([PJ.Doc] -> PJ.Doc) -> ([Doc] -> Doc)
liftSep f ds = Doc (\e -> f [ d e | Doc d <- ds ])
infixl 6 <>, <+>
(<>) :: Doc -> Doc -> Doc
(<>) = liftPJ2 (PJ.<>)
(<+>) :: Doc -> Doc -> Doc
(<+>) = liftPJ2 (PJ.<+>)
infixl 5 $$
($$) :: Doc -> Doc -> Doc
($$) = liftPJ2 (PJ.$$)
sep :: [Doc] -> Doc
sep = liftSep PJ.sep
fsep :: [Doc] -> Doc
fsep = liftSep PJ.fsep
hsep :: [Doc] -> Doc
hsep = liftSep PJ.hsep
hcat :: [Doc] -> Doc
hcat = liftSep PJ.hcat
vcat :: [Doc] -> Doc
vcat = liftSep PJ.vcat
hang :: Doc -> Int -> Doc -> Doc
hang (Doc p) i (Doc q) = Doc (\e -> PJ.hang (p e) i (q e))
nest :: Int -> Doc -> Doc
nest n = liftPJ1 (PJ.nest n)
parens :: Doc -> Doc
parens = liftPJ1 PJ.parens
braces :: Doc -> Doc
braces = liftPJ1 PJ.braces
brackets :: Doc -> Doc
brackets = liftPJ1 PJ.brackets
quotes :: Doc -> Doc
quotes = liftPJ1 PJ.quotes
punctuate :: Doc -> [Doc] -> [Doc]
punctuate p = go
where
go (d:ds) | null ds = [d]
| otherwise = d <> p : go ds
go [] = []
text :: String -> Doc
text s = liftPJ (PJ.text s)
char :: Char -> Doc
char c = liftPJ (PJ.char c)
integer :: Integer -> Doc
integer i = liftPJ (PJ.integer i)
int :: Int -> Doc
int i = liftPJ (PJ.int i)
comma :: Doc
comma = liftPJ PJ.comma
empty :: Doc
empty = liftPJ PJ.empty
colon :: Doc
colon = liftPJ PJ.colon
instance PP T.Text where
ppPrec _ str = text (T.unpack str)
instance PP Ident where
ppPrec _ i = text (T.unpack (identText i))