Skip to content

Instantly share code, notes, and snippets.

@donsbot
Created February 21, 2022 04:21
Show Gist options
  • Save donsbot/08302e0ff4ba3c3d580129c04df67584 to your computer and use it in GitHub Desktop.
Save donsbot/08302e0ff4ba3c3d580129c04df67584 to your computer and use it in GitHub Desktop.
{-
Copyright (c) Meta Platforms, Inc. and affiliates.
All rights reserved.
This source code is licensed under the BSD-style license found in the
LICENSE file in the root directory of this source tree.
-}
{-# LANGUAGE TypeApplications #-}
module BareBones (main) where
import Control.Exception
import Test.HUnit
import Data.List
import qualified Data.Text as Text
import TestRunner
import Glean.Backend as Backend
import Glean.Init
import Glean.Query.Angle as Angle
import Glean.Query.Thrift as Thrift
import qualified Glean.Schema.Cxx1.Types as Cxx
import Glean.Typed hiding (end)
import Glean.Types
import Glean.Database.Test
import TestDB
goodTest :: IO ()
goodTest = withTestDB [setMemoryStorage] $ \env repo -> do
-- "Literal fact ID with the correct type
print "begin"
(r :: Either SomeException [Cxx.Name]) <- try $ runQuery_ env repo $ angle @Cxx.Name "$cxx1.Name 1026"
print r
assertBool "ok" True
badTest :: IO ()
badTest = withTestDB [setMemoryStorage] $ \env repo -> do
-- "Literal fact ID with the correct type (i.e. type is really a Cxx.Name)
print "begin"
-- generatse SIGABRT
(r :: Either Glean.Types.Exception [Cxx.Type]) <- try $ runQuery_ env repo $ angle @Cxx.Type "$cxx1.Type 1026"
-- Right [Name {name_id = 1026, name_key = Just "foo"}]
print r
assertBool "ok" True
main :: IO ()
main = do
badTest
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment