{-# LANGUAGE TemplateHaskell, ScopedTypeVariables, TypeFamilies, DataKinds, PolyKinds, UndecidableInstances, GADTs, RankNTypes, TypeApplications #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Singletons.Prelude.Maybe -- Copyright : (C) 2013-2014 Richard Eisenberg, Jan Stolarek -- License : BSD-style (see LICENSE) -- Maintainer : Ryan Scott -- Stability : experimental -- Portability : non-portable -- -- Defines functions and datatypes relating to the singleton for 'Maybe', -- including a singletons version of all the definitions in @Data.Maybe@. -- -- Because many of these definitions are produced by Template Haskell, -- it is not possible to create proper Haddock documentation. Please look -- up the corresponding operation in @Data.Maybe@. Also, please excuse -- the apparent repeated variable names. This is due to an interaction -- between Template Haskell and Haddock. -- ---------------------------------------------------------------------------- module Data.Singletons.Prelude.Maybe ( -- The 'Maybe' singleton Sing, SMaybe(..), -- * Singletons from @Data.Maybe@ maybe_, Maybe_, sMaybe_, -- | The preceding two definitions are derived from the function 'maybe' in -- @Data.Maybe@. The extra underscore is to avoid name clashes with the type -- 'Maybe'. IsJust, sIsJust, IsNothing, sIsNothing, FromJust, sFromJust, FromMaybe, sFromMaybe, ListToMaybe, sListToMaybe, MaybeToList, sMaybeToList, CatMaybes, sCatMaybes, MapMaybe, sMapMaybe, -- * Defunctionalization symbols NothingSym0, JustSym0, JustSym1, Maybe_Sym0, Maybe_Sym1, Maybe_Sym2, Maybe_Sym3, IsJustSym0, IsJustSym1, IsNothingSym0, IsNothingSym1, FromJustSym0, FromJustSym1, FromMaybeSym0, FromMaybeSym1, FromMaybeSym2, ListToMaybeSym0, ListToMaybeSym1, MaybeToListSym0, MaybeToListSym1, CatMaybesSym0, CatMaybesSym1, MapMaybeSym0, MapMaybeSym1, MapMaybeSym2 ) where import Data.Singletons.Prelude.Instances import Data.Singletons.Single import Data.Singletons.TypeLits $(singletons [d| -- Renamed to avoid name clash -- -| The 'maybe' function takes a default value, a function, and a 'Maybe' -- value. If the 'Maybe' value is 'Nothing', the function returns the -- default value. Otherwise, it applies the function to the value inside -- the 'Just' and returns the result. maybe_ :: b -> (a -> b) -> Maybe a -> b maybe_ n _ Nothing = n maybe_ _ f (Just x) = f x |]) $(