Created
May 27, 2025 11:00
-
-
Save ymdfield/263ee0ded63491efbf1c63bdc39779cf to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| #!/usr/bin/env -S cabal run -v1 | |
| {- cabal: | |
| build-depends: base, pipes | |
| ghc-options: -Wall | |
| -} | |
| {-# LANGUAGE GHC2021 #-} | |
| import Pipes | |
| import Control.Applicative | |
| main :: IO () | |
| main = runListT $ do | |
| x :: Int <- pure 1 <|> pure 2 <|> pure 3 | |
| liftIO $ print x | |
| -- > main | |
| -- 1 | |
| -- 2 | |
| -- 3 |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Bluefin equivalent:
{-# LANGUAGE GHC2021 #-} import Bluefin.Compound (mapHandle, useImpl, useImplIn, useImplUnder) import Bluefin.Eff (Eff, runEff, (:&), (:>)) import Bluefin.IO (effIO) import Bluefin.Stream (Stream, forEach, ignoreStream, yield) import Control.Applicative (Alternative, empty, (<|>)) import Control.Monad (ap) newtype Logic es a = MkLogic {enumerate :: forall e. Stream a e -> Eff (e :& es) ()} instance Functor (Logic es) where fmap f (MkLogic k) = MkLogic (\y -> forEach (useImplUnder . k) $ \a -> yield y (f a)) instance Applicative (Logic es) where pure a = MkLogic (\y -> yield y a) (<*>) = ap instance Monad (Logic es) where return = pure MkLogic k >>= f = MkLogic $ \y -> do forEach (useImplUnder . k) $ \a -> do enumerate (f a) y instance Alternative (Logic es) where empty = MkLogic (\_ -> pure ()) MkLogic p1 <|> MkLogic p2 = MkLogic $ \y -> do p1 y p2 y runLogic :: (e :> es) => Stream a e -> Logic es a -> Eff es () runLogic y l = useImplIn (enumerate l) (mapHandle y) liftEff :: Eff es () -> Logic es () liftEff m = MkLogic (\_ -> useImpl m) -- ghci> main -- 1 -- 2 -- 3 main :: IO () main = runEff $ \io -> ignoreStream $ \y -> runLogic y $ do x :: Int <- pure 1 <|> pure 2 <|> pure 3 liftEff (effIO io (print x))