Moving from govendor to dep, updated dependencies (#48)

* Moving from govendor to dep.

* Making the pull request template more friendly.

* Fixing akward space in PR template.

* goimports run on whole project using ` goimports -w $(find . -type f -name '*.go' -not -path "./vendor/*" -not -path "./gen-go/*")`

source of command: https://gist.github.com/bgentry/fd1ffef7dbde01857f66
This commit is contained in:
Renan DelValle 2018-01-07 13:13:47 -08:00 committed by GitHub
parent 9631aa3aab
commit 8d445c1c77
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
2186 changed files with 400410 additions and 352 deletions

View file

@ -0,0 +1,91 @@
--
-- Licensed to the Apache Software Foundation (ASF) under one
-- or more contributor license agreements. See the NOTICE file
-- distributed with this work for additional information
-- regarding copyright ownership. The ASF licenses this file
-- to you under the Apache License, Version 2.0 (the
-- "License"); you may not use this file except in compliance
-- with the License. You may obtain a copy of the License at
--
-- http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing,
-- software distributed under the License is distributed on an
-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
-- KIND, either express or implied. See the License for the
-- specific language governing permissions and limitations
-- under the License.
--
module BinarySpec where
import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Lazy.Char8 as C
import Thrift.Types
import Thrift.Transport
import Thrift.Transport.Memory
import Thrift.Protocol
import Thrift.Protocol.Binary
spec :: Spec
spec = do
describe "BinaryProtocol" $ do
describe "double" $ do
it "writes in big endian order" $ do
let val = 2 ** 53
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
writeVal proto (TDouble val)
bin <- tRead trans 8
(LBS.unpack bin) `shouldBe`[67, 64, 0, 0, 0, 0, 0, 0]
it "reads in big endian order" $ do
let bin = LBS.pack [67, 64, 0, 0, 0, 0, 0, 0]
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
tWrite trans bin
val <- readVal proto T_DOUBLE
val `shouldBe` (TDouble $ 2 ** 53)
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
writeVal proto $ TDouble val
val2 <- readVal proto T_DOUBLE
val2 `shouldBe` (TDouble val)
describe "string" $ do
it "writes" $ do
let val = C.pack "aaa"
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
writeVal proto (TString val)
bin <- tRead trans 7
(LBS.unpack bin) `shouldBe` [0, 0, 0, 3, 97, 97, 97]
describe "binary" $ do
it "writes" $ do
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
writeVal proto (TBinary $ LBS.pack [42, 43, 44])
bin <- tRead trans 100
(LBS.unpack bin) `shouldBe` [0, 0, 0, 3, 42, 43, 44]
it "reads" $ do
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
tWrite trans $ LBS.pack [0, 0, 0, 3, 42, 43, 44]
val <- readVal proto (T_BINARY)
val `shouldBe` (TBinary $ LBS.pack [42, 43, 44])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = BinaryProtocol trans
writeVal proto (TBinary $ LBS.pack val)
val2 <- readVal proto (T_BINARY)
val2 `shouldBe` (TBinary $ LBS.pack val)

View file

@ -0,0 +1,81 @@
--
-- Licensed to the Apache Software Foundation (ASF) under one
-- or more contributor license agreements. See the NOTICE file
-- distributed with this work for additional information
-- regarding copyright ownership. The ASF licenses this file
-- to you under the Apache License, Version 2.0 (the
-- "License"); you may not use this file except in compliance
-- with the License. You may obtain a copy of the License at
--
-- http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing,
-- software distributed under the License is distributed on an
-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
-- KIND, either express or implied. See the License for the
-- specific language governing permissions and limitations
-- under the License.
--
module CompactSpec where
import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import qualified Data.ByteString.Lazy as LBS
import Thrift.Types
import Thrift.Transport
import Thrift.Transport.Memory
import Thrift.Protocol
import Thrift.Protocol.Compact
spec :: Spec
spec = do
describe "CompactProtocol" $ do
describe "double" $ do
it "writes in little endian order" $ do
let val = 2 ** 53
trans <- openMemoryBuffer
let proto = CompactProtocol trans
writeVal proto (TDouble val)
bin <- tReadAll trans 8
(LBS.unpack bin) `shouldBe`[0, 0, 0, 0, 0, 0, 64, 67]
it "reads in little endian order" $ do
let bin = LBS.pack [0, 0, 0, 0, 0, 0, 64, 67]
trans <- openMemoryBuffer
let proto = CompactProtocol trans
tWrite trans bin
val <- readVal proto T_DOUBLE
val `shouldBe` (TDouble $ 2 ** 53)
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = CompactProtocol trans
writeVal proto $ TDouble val
val2 <- readVal proto T_DOUBLE
val2 `shouldBe` (TDouble val)
describe "binary" $ do
it "writes" $ do
trans <- openMemoryBuffer
let proto = CompactProtocol trans
writeVal proto (TBinary $ LBS.pack [42, 43, 44])
bin <- tRead trans 100
(LBS.unpack bin) `shouldBe` [3, 42, 43, 44]
it "reads" $ do
trans <- openMemoryBuffer
let proto = CompactProtocol trans
tWrite trans $ LBS.pack [3, 42, 43, 44]
val <- readVal proto (T_BINARY)
val `shouldBe` (TBinary $ LBS.pack [42, 43, 44])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = CompactProtocol trans
writeVal proto (TBinary $ LBS.pack val)
val2 <- readVal proto (T_BINARY)
val2 `shouldBe` (TBinary $ LBS.pack val)

View file

@ -0,0 +1,225 @@
--
-- Licensed to the Apache Software Foundation (ASF) under one
-- or more contributor license agreements. See the NOTICE file
-- distributed with this work for additional information
-- regarding copyright ownership. The ASF licenses this file
-- to you under the Apache License, Version 2.0 (the
-- "License"); you may not use this file except in compliance
-- with the License. You may obtain a copy of the License at
--
-- http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing,
-- software distributed under the License is distributed on an
-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
-- KIND, either express or implied. See the License for the
-- specific language governing permissions and limitations
-- under the License.
--
module JSONSpec where
import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Lazy.Char8 as C
import Thrift.Types
import Thrift.Transport
import Thrift.Transport.Memory
import Thrift.Protocol
import Thrift.Protocol.JSON
tString :: [Char] -> ThriftVal
tString = TString . C.pack
spec :: Spec
spec = do
describe "JSONProtocol" $ do
describe "bool" $ do
it "writes true as 1" $ do
let val = True
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TBool val)
bin <-tRead trans 100
(C.unpack bin) `shouldBe` ['1']
it "writes false as 0" $ do
let val = False
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TBool val)
bin <- tRead trans 100
(C.unpack bin) `shouldBe` ['0']
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto $ TBool val
val2 <- readVal proto T_BOOL
val2 `shouldBe` (TBool val)
describe "string" $ do
it "writes" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TString $ C.pack "\"a")
bin <- tRead trans 100
(C.unpack bin) `shouldBe` "\"\\\"a\""
it "reads" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans $ C.pack "\"\\\"a\""
val <- readVal proto (T_STRING)
val `shouldBe` (TString $ C.pack "\"a")
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TString $ C.pack val)
val2 <- readVal proto (T_STRING)
val2 `shouldBe` (TString $ C.pack val)
describe "binary" $ do
it "writes with padding" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TBinary $ LBS.pack [1])
bin <- tRead trans 100
(C.unpack bin) `shouldBe` "\"AQ==\""
it "reads with padding" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans $ C.pack "\"AQ==\""
val <- readVal proto (T_BINARY)
val `shouldBe` (TBinary $ LBS.pack [1])
it "reads without padding" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans $ C.pack "\"AQ\""
val <- readVal proto (T_BINARY)
val `shouldBe` (TBinary $ LBS.pack [1])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TBinary $ LBS.pack val)
val2 <- readVal proto (T_BINARY)
val2 `shouldBe` (TBinary $ LBS.pack val)
describe "list" $ do
it "writes empty list" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TList T_BYTE [])
bin <- tRead trans 100
(C.unpack bin) `shouldBe` "[\"i8\",0]"
it "reads empty" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",0]")
val <- readVal proto (T_LIST T_BYTE)
val `shouldBe` (TList T_BYTE [])
it "writes single element" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TList T_BYTE [TByte 0])
bin <- tRead trans 100
(C.unpack bin) `shouldBe` "[\"i8\",1,0]"
it "reads single element" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",1,0]")
val <- readVal proto (T_LIST T_BYTE)
val `shouldBe` (TList T_BYTE [TByte 0])
it "reads elements" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",2,42, 43]")
val <- readVal proto (T_LIST T_BYTE)
val `shouldBe` (TList T_BYTE [TByte 42, TByte 43])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto $ (TList T_STRING $ map tString val)
val2 <- readVal proto $ T_LIST T_STRING
val2 `shouldBe` (TList T_STRING $ map tString val)
describe "set" $ do
it "writes empty" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TSet T_BYTE [])
bin <- tRead trans 100
(C.unpack bin) `shouldBe` "[\"i8\",0]"
it "reads empty" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",0]")
val <- readVal proto (T_SET T_BYTE)
val `shouldBe` (TSet T_BYTE [])
it "reads single element" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",1,0]")
val <- readVal proto (T_SET T_BYTE)
val `shouldBe` (TSet T_BYTE [TByte 0])
it "reads elements" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",2,42, 43]")
val <- readVal proto (T_SET T_BYTE)
val `shouldBe` (TSet T_BYTE [TByte 42, TByte 43])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto $ (TSet T_STRING $ map tString val)
val2 <- readVal proto $ T_SET T_STRING
val2 `shouldBe` (TSet T_STRING $ map tString val)
describe "map" $ do
it "writes empty" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto (TMap T_BYTE T_BYTE [])
bin <- tRead trans 100
(C.unpack bin) `shouldBe`"[\"i8\",\"i8\",0,{}]"
it "reads empty" $ do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack "[\"i8\",\"i8\",0,{}]")
val <- readVal proto (T_MAP T_BYTE T_BYTE)
val `shouldBe` (TMap T_BYTE T_BYTE [])
it "reads string-string" $ do
let bin = "[\"str\",\"str\",2,{\"a\":\"2\",\"b\":\"blah\"}]"
trans <- openMemoryBuffer
let proto = JSONProtocol trans
tWrite trans (C.pack bin)
val <- readVal proto (T_MAP T_STRING T_STRING)
val`shouldBe` (TMap T_STRING T_STRING [(tString "a", tString "2"), (tString "b", tString "blah")])
prop "round trip" $ \val -> do
trans <- openMemoryBuffer
let proto = JSONProtocol trans
writeVal proto $ (TMap T_STRING T_STRING $ map toKV val)
val2 <- readVal proto $ T_MAP T_STRING T_STRING
val2 `shouldBe` (TMap T_STRING T_STRING $ map toKV val)
where
toKV v = (tString v, tString v)

38
vendor/git.apache.org/thrift.git/lib/hs/test/Spec.hs generated vendored Normal file
View file

@ -0,0 +1,38 @@
--
-- Licensed to the Apache Software Foundation (ASF) under one
-- or more contributor license agreements. See the NOTICE file
-- distributed with this work for additional information
-- regarding copyright ownership. The ASF licenses this file
-- to you under the Apache License, Version 2.0 (the
-- "License"); you may not use this file except in compliance
-- with the License. You may obtain a copy of the License at
--
-- http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing,
-- software distributed under the License is distributed on an
-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
-- KIND, either express or implied. See the License for the
-- specific language governing permissions and limitations
-- under the License.
--
-- Our CI does not work well with auto discover.
-- Need to add build-time PATH variable to hspec-discover dir from CMake
-- or install hspec system-wide for the following to work.
-- {-# OPTIONS_GHC -F -pgmF hspec-discover #-}
import Test.Hspec
import qualified BinarySpec
import qualified CompactSpec
import qualified JSONSpec
main :: IO ()
main = hspec spec
spec :: Spec
spec = do
describe "Binary" BinarySpec.spec
describe "Compact" CompactSpec.spec
describe "JSON" JSONSpec.spec