File: RenderingTests.hs

package info (click to toggle)
haskell-hslua-packaging 2.3.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 160 kB
  • sloc: haskell: 1,296; makefile: 5
file content (141 lines) | stat: -rw-r--r-- 3,842 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
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
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
{-|
Module      : HsLua.Packaging.RenderingTests
Copyright   : © 2020-2024 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb@hslua.org>

Tests for calling exposed Haskell functions.
-}
module HsLua.Packaging.RenderingTests (tests) where

import Data.Maybe (fromMaybe)
import Data.Version (makeVersion)
import HsLua.Packaging.Convenience
import HsLua.Packaging.Function
import HsLua.Packaging.Module
import HsLua.Packaging.Rendering
import HsLua.Marshalling
  (peekIntegral, peekRealFloat, pushIntegral, pushRealFloat)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit ((@=?), testCase)

import qualified Data.Text as T
import qualified HsLua.Core as Lua

-- | Calling Haskell functions from Lua.
tests :: TestTree
tests = testGroup "Rendering" $
  let factorialDocs = T.intercalate "\n"
        [ "factorial (n)"
        , ""
        , "Calculates the factorial of a positive integer."
        , ""
        , "*Since: 1.0.0*"
        , ""
        , "Parameters:"
        , ""
        , "n"
        , ":   number for which the factorial is computed (integer)"
        , ""
        , "Returns:"
        , ""
        , " -  factorial (integer)"
        ]
      nrootDocs = T.intercalate "\n"
        [ "nroot (x, n)"
        , ""
        , "Parameters:"
        , ""
        , "x"
        , ":    (number)"
        , ""
        , "n"
        , ":    (integer)"
        , ""
        , "Returns:"
        , ""
        , " -  nth root (number)"
        ]
      eulerDocs = T.intercalate "\n"
        [ "euler_mascheroni"
        , ""
        , "Euler-Mascheroni constant"
        ]
  in
    [ testGroup "Function"
      [ testCase "rendered docs" $
        factorialDocs @=?
        renderFunction factorial
      ]
    , testGroup "Module"
      [ testCase "module docs"
        (T.unlines
         [ "# mymath"
         , ""
         , "A math module."
         , ""
         , "### " `T.append` eulerDocs
         , ""
         , "## Functions"
         , ""
         , "### " `T.append` factorialDocs
         , ""
         , "### " `T.append` nrootDocs
         ] @=?
         render mymath)
      ]
    ]

-- | Calculate the nth root of a number. Defaults to square root.
nroot :: DocumentedFunction Lua.Exception
nroot = defun "nroot" (liftPure2 nroot')
  <#> parameter (peekRealFloat @Double) "number" "x" ""
  <#> opt (integralParam @Int "n" "")
  =#> functionResult pushRealFloat "number" "nth root"
  where
    nroot' :: Double -> Maybe Int -> Double
    nroot' x nOpt =
      let n = fromMaybe 2 nOpt
      in x ** (1 / fromIntegral n)

mymath :: Module Lua.Exception
mymath = Module
  { moduleName = "mymath"
  , moduleDescription = "A math module."
  , moduleFields = [euler_mascheroni]
  , moduleFunctions = [ factorial, nroot ]
  , moduleOperations = []
  , moduleTypeInitializers = []
  }

-- | Euler-Mascheroni constant
euler_mascheroni :: Field Lua.Exception
euler_mascheroni = Field
  { fieldName = "euler_mascheroni"
  , fieldType = "number"
  , fieldDescription = "Euler-Mascheroni constant"
  , fieldPushValue = pushRealFloat @Double
                     0.57721566490153286060651209008240243
  }

-- | Calculate the factorial of a number.
factorial :: DocumentedFunction Lua.Exception
factorial = defun "factorial"
  ### liftPure (\n -> product [1..n])
  <#> factorialParam
  =#> factorialResult
  #? "Calculates the factorial of a positive integer."
  `since` makeVersion [1,0,0]

factorialParam :: Parameter Lua.Exception Integer
factorialParam =
  parameter peekIntegral "integer"
    "n"
    "number for which the factorial is computed"

factorialResult :: FunctionResults Lua.Exception Integer
factorialResult =
  functionResult pushIntegral "integer" "factorial"