{-# LANGUAGE TypeFamilies #-}
{- |
LLVM counterpart to 'Maybe' datatype.
-}
module LLVM.Extra.Maybe (
   Maybe.T(..),
   Maybe.run,
   Maybe.for,
   Maybe.select,
   Maybe.alternative,
   Maybe.fromBool,
   Maybe.toBool,
   Maybe.getIsNothing,
   Maybe.just,
   nothing,
   Maybe.sequence,
   Maybe.traverse,
   Maybe.lift2,
   Maybe.liftM2,

   loopWithExit,
   ) where

import qualified LLVM.Extra.Tuple as Tuple
import qualified LLVM.Extra.MaybePrivate as Maybe
import qualified LLVM.Extra.Control as C

import LLVM.Core (CodeGenFunction, )


nothing :: (Tuple.Undefined a) => Maybe.T a
nothing = Maybe.nothing Tuple.undef


loopWithExit ::
   Tuple.Phi a =>
   a ->
   (a -> CodeGenFunction r (Maybe.T c, b)) ->
   ((c,b) -> CodeGenFunction r a) ->
   CodeGenFunction r b
loopWithExit start check body =
   fmap snd $
   C.loopWithExit start
      (\a -> do
         (mc,b) <- check a
         let (j,c) = Maybe.toBool mc
         return (j, (c,b)))
      body