never executed always true always false
1 -- Strict counterparts to common data structures,
2 -- e.g. tuples, lists, maybes, etc.
3 --
4 -- Import this module qualified as Strict.
5
6 {-# LANGUAGE DeriveDataTypeable #-}
7 {-# LANGUAGE DeriveTraversable #-}
8
9 module GHC.Data.Strict (
10 Maybe(Nothing, Just),
11 fromMaybe,
12 Pair(And),
13
14 -- Not used at the moment:
15 --
16 -- Either(Left, Right),
17 -- List(Nil, Cons),
18 ) where
19
20 import GHC.Prelude hiding (Maybe(..), Either(..))
21 import Control.Applicative
22 import Data.Semigroup
23 import Data.Data
24
25 data Maybe a = Nothing | Just !a
26 deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data)
27
28 fromMaybe :: a -> Maybe a -> a
29 fromMaybe d Nothing = d
30 fromMaybe _ (Just x) = x
31
32 apMaybe :: Maybe (a -> b) -> Maybe a -> Maybe b
33 apMaybe (Just f) (Just x) = Just (f x)
34 apMaybe _ _ = Nothing
35
36 altMaybe :: Maybe a -> Maybe a -> Maybe a
37 altMaybe Nothing r = r
38 altMaybe l _ = l
39
40 instance Semigroup a => Semigroup (Maybe a) where
41 Nothing <> b = b
42 a <> Nothing = a
43 Just a <> Just b = Just (a <> b)
44
45 instance Semigroup a => Monoid (Maybe a) where
46 mempty = Nothing
47
48 instance Applicative Maybe where
49 pure = Just
50 (<*>) = apMaybe
51
52 instance Alternative Maybe where
53 empty = Nothing
54 (<|>) = altMaybe
55
56 data Pair a b = !a `And` !b
57 deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data)
58
59 -- The definitions below are commented out because they are
60 -- not used anywhere in the compiler, but are useful to showcase
61 -- the intent behind this module (i.e. how it may evolve).
62 --
63 -- data Either a b = Left !a | Right !b
64 -- deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data)
65 --
66 -- data List a = Nil | !a `Cons` !(List a)
67 -- deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Data)