File: Test.hs

package info (click to toggle)
haskell-czipwith 1.0.1.4-1
  • links: PTS
  • area: main
  • in suites: bookworm
  • size: 80 kB
  • sloc: haskell: 280; makefile: 6
file content (80 lines) | stat: -rw-r--r-- 1,707 bytes parent folder | download | duplicates (2)
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
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}

module Main where



import Data.CZipWith
import Data.Functor.Identity
import Data.Functor.Const



data A f = A
  { a_str :: f String
  , a_bool :: f Bool
  }

data B f = B
  { b_int :: f Int
  , b_float :: f Float
  , b_a :: A f
  }

deriving instance Show (A Identity)
deriving instance Eq (A Identity)
deriving instance Eq (A (Const Bool))
deriving instance Eq (A Maybe)
deriving instance Eq (B Identity)
deriving instance Eq (B (Const Bool))
deriving instance Eq (B Maybe)


deriveCZipWith ''A
deriveCZipWith ''B

deriveCPointed ''A
deriveCPointed ''B

deriveCZipWithM ''A
deriveCZipWithM ''B

main :: IO ()
main = do
  let x1 =
        B (Identity 12) (Identity 3.1) (A (Identity "string") (Identity True))
  let x2 = B (Just 1) Nothing (A (Just "just") Nothing)
  let x3 = cZipWith
        (\x my -> case my of
          Nothing -> x
          Just y  -> Identity y
        )
        x1
        x2
  errorIf
      (x3 /= B (Identity 1) (Identity 3.1) (A (Identity "just") (Identity True))
      )
    $ return ()
  let (Identity x4) = cZipWithM
        (\x my -> Identity $ case my of
          Nothing -> x
          Just y  -> Identity y
        )
        x1
        x2
  errorIf
      (x4 /= B (Identity 1) (Identity 3.1) (A (Identity "just") (Identity True))
      )
    $ return ()
  let (Identity x5) = cTraverse Identity x2
  errorIf (x2 /= x5) $ return ()
  let x6 = cPoint (Const True)
  errorIf (x6 /= B (Const True) (Const True) (A (Const True) (Const True)))
    $ return ()
  putStrLn "no errors found!"

errorIf :: Bool -> a -> a
errorIf False = id
errorIf True  = error "errorIf"