File: MarshallingTests.hs

package info (click to toggle)
haskell-hslua-marshalling 2.3.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 148 kB
  • sloc: haskell: 1,407; makefile: 3
file content (58 lines) | stat: -rw-r--r-- 1,779 bytes parent folder | download
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
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module      : HsLua.MarshallingTests
Copyright   : © 2020-2024 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb@hslua.org>
Stability   : alpha
Portability : OverloadedStrings, TypeApplications

Test marshalling of basic values.
-}
module HsLua.MarshallingTests (tests) where

import Control.Monad ((<$!>))
import HsLua.Core
import HsLua.Marshalling.Peek
import HsLua.Marshalling.Peekers
import HsLua.Marshalling.Push
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HsLua ((=:), shouldBeResultOf)
import qualified HsLua.Marshalling.PeekTests
import qualified HsLua.Marshalling.PeekersTests
import qualified HsLua.Marshalling.PushTests
import qualified HsLua.Marshalling.UserdataTests

-- | Tests for value marshalling.
tests :: TestTree
tests = testGroup "Marshalling"
  [ HsLua.Marshalling.PeekTests.tests
  , HsLua.Marshalling.PeekersTests.tests
  , HsLua.Marshalling.PushTests.tests
  , HsLua.Marshalling.UserdataTests.tests
  , testGroup "nested"
    [ "deeply nested list" =:
      Success (mkDeeplyNested 500) `shouldBeResultOf` do
        pushNested (mkDeeplyNested 500)
        runPeek $ peekNested top
    ]
  ]

mkDeeplyNested :: Int -> Nested
mkDeeplyNested i = foldr (\_ n -> List [n]) (Element i) [1..i]

pushNested :: LuaError e => Pusher e Nested
pushNested = \case
  Element i   -> pushIntegral i
  List nested -> pushList pushNested nested

peekNested :: LuaError e => Peeker e Nested
peekNested idx = do
  liftLua (ltype idx) >>= \case
    TypeNumber  -> Element <$!> peekIntegral idx
    TypeTable   -> (List   <$!> peekList peekNested idx)
    _           -> failPeek "you dun goofed"

data Nested = Element Int | List [Nested]
  deriving (Eq, Show)