{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Array.Accelerate.Data.Maybe (
Maybe(..), pattern Nothing_, pattern Just_,
maybe, isJust, isNothing, fromMaybe, fromJust, justs,
) where
import Data.Array.Accelerate.AST.Idx
import Data.Array.Accelerate.Language
import Data.Array.Accelerate.Lift
import Data.Array.Accelerate.Pattern.Maybe
import Data.Array.Accelerate.Prelude
import Data.Array.Accelerate.Smart
import Data.Array.Accelerate.Sugar.Array ( Array, Vector )
import Data.Array.Accelerate.Sugar.Elt
import Data.Array.Accelerate.Sugar.Shape ( Shape, Slice, (:.) )
import Data.Array.Accelerate.Type
import Data.Array.Accelerate.Classes.Eq
import Data.Array.Accelerate.Classes.Ord
import Data.Array.Accelerate.Data.Functor
import Data.Array.Accelerate.Data.Monoid
import Data.Array.Accelerate.Data.Semigroup
import Data.Maybe ( Maybe(..) )
import Prelude ( ($), (.) )
isNothing :: Elt a => Exp (Maybe a) -> Exp Bool
isNothing = not . isJust
isJust :: Elt a => Exp (Maybe a) -> Exp Bool
isJust (Exp x) = Exp $ SmartExp $ (SmartExp $ Prj PairIdxLeft x) `Pair` SmartExp Nil
fromMaybe :: Elt a => Exp a -> Exp (Maybe a) -> Exp a
fromMaybe d = match \case
Nothing_ -> d
Just_ x -> x
fromJust :: Elt a => Exp (Maybe a) -> Exp a
fromJust (Exp x) = Exp $ SmartExp (PairIdxRight `Prj` SmartExp (PairIdxRight `Prj` x))
maybe :: (Elt a, Elt b) => Exp b -> (Exp a -> Exp b) -> Exp (Maybe a) -> Exp b
maybe d f = match \case
Nothing_ -> d
Just_ x -> f x
justs :: (Shape sh, Slice sh, Elt a)
=> Acc (Array (sh:.Int) (Maybe a))
-> Acc (Vector a, Array sh Int)
justs xs = compact (map isJust xs) (map fromJust xs)
instance Functor Maybe where
fmap f = match \case
Nothing_ -> Nothing_
Just_ x -> Just_ (f x)
instance Eq a => Eq (Maybe a) where
(==) = match go
where
go Nothing_ Nothing_ = True_
go (Just_ x) (Just_ y) = x == y
go _ _ = False_
instance Ord a => Ord (Maybe a) where
compare = match go
where
go (Just_ x) (Just_ y) = compare x y
go Nothing_ Nothing_ = EQ_
go Nothing_ Just_{} = LT_
go Just_{} Nothing_{} = GT_
instance (Monoid (Exp a), Elt a) => Monoid (Exp (Maybe a)) where
mempty = Nothing_
instance (Semigroup (Exp a), Elt a) => Semigroup (Exp (Maybe a)) where
ma <> mb = cond (isNothing ma) mb
$ cond (isNothing mb) mb
$ lift (Just (fromJust ma <> fromJust mb))
instance (Lift Exp a, Elt (Plain a)) => Lift Exp (Maybe a) where
type Plain (Maybe a) = Maybe (Plain a)
lift Nothing = Nothing_
lift (Just a) = Just_ (lift a)