module LinearScan.Maybe where import Debug.Trace (trace, traceShow, traceShowId) import qualified Prelude import qualified Data.IntMap import qualified Data.IntSet import qualified Data.List import qualified Data.Ord import qualified Data.Functor.Identity import qualified Hask.Utils fromMaybe :: a1 -> (Prelude.Maybe a1) -> a1 fromMaybe x my = case my of { Prelude.Just z -> z; Prelude.Nothing -> x} maybe :: a1 -> (a2 -> a1) -> (Prelude.Maybe a2) -> a1 maybe x f my = case my of { Prelude.Just z -> f z; Prelude.Nothing -> x} isJust :: (Prelude.Maybe a1) -> Prelude.Bool isJust x = case x of { Prelude.Just a -> Prelude.True; Prelude.Nothing -> Prelude.False} option_map :: (a1 -> a2) -> (Prelude.Maybe a1) -> Prelude.Maybe a2 option_map f x = case x of { Prelude.Just x0 -> Prelude.Just (f x0); Prelude.Nothing -> Prelude.Nothing} option_choose :: (Prelude.Maybe a1) -> (Prelude.Maybe a1) -> Prelude.Maybe a1 option_choose x y = case x of { Prelude.Just a -> x; Prelude.Nothing -> y}