mirror of
https://github.com/rowtype-yoga/purescript-lazy-joe.git
synced 2024-12-01 16:49:03 +03:00
Relax to MonadEffect
This commit is contained in:
parent
dcc2e65ea3
commit
7495f3404f
@ -7,6 +7,7 @@ import Control.Promise as Promise
|
||||
import Data.Function.Uncurried (Fn1, Fn2, Fn3, mkFn2, mkFn3, runFn1, runFn2, runFn3)
|
||||
import Effect (Effect)
|
||||
import Effect.Aff.Class (class MonadAff, liftAff)
|
||||
import Effect.Class (class MonadEffect, liftEffect)
|
||||
import Unsafe.Coerce (unsafeCoerce)
|
||||
|
||||
foreign import fromImpl :: forall mod. String -> Effect (Promise mod)
|
||||
@ -38,12 +39,12 @@ foreign import effectful2 :: forall a b c. Fn2 a b c -> a -> b -> Effect c
|
||||
|
||||
foreign import effectful1 :: forall a b. Fn1 a b -> a -> Effect b
|
||||
|
||||
instance Effectful (Fn3 a b c d) (a -> b -> c -> Effect d) where
|
||||
effectful f = \a -> \b -> \c -> effectful3 f a b c
|
||||
else instance Effectful (Fn2 a b c) (a -> b -> Effect c) where
|
||||
effectful f = \a -> \b -> effectful2 f a b
|
||||
else instance Effectful (Fn1 a b) (a -> Effect b) where
|
||||
effectful f = \a -> effectful1 f a
|
||||
instance MonadEffect eff => Effectful (Fn3 a b c d) (a -> b -> c -> eff d) where
|
||||
effectful f = \a -> \b -> \c -> effectful3 f a b c # liftEffect
|
||||
else instance MonadEffect eff =>Effectful (Fn2 a b c) (a -> b -> eff c) where
|
||||
effectful f = \a -> \b -> effectful2 f a b # liftEffect
|
||||
else instance MonadEffect eff =>Effectful (Fn1 a b) (a -> eff b) where
|
||||
effectful f = \a -> effectful1 f a # liftEffect
|
||||
|
||||
foreign import scoped3 :: forall mod a b c d. mod -> Fn3 a b c d -> a -> b -> c -> d
|
||||
|
||||
|
@ -3,10 +3,8 @@ module Test.Main where
|
||||
import Prelude
|
||||
|
||||
import Effect (Effect)
|
||||
import Effect.Aff (launchAff_)
|
||||
import Effect.Aff (Aff, launchAff_)
|
||||
import Effect.Class.Console (log)
|
||||
|
||||
import Effect.Class (liftEffect)
|
||||
import Lazy.Joe (effectful, fromDefault, scoped, variadic)
|
||||
|
||||
main :: Effect Unit
|
||||
@ -24,23 +22,22 @@ main = launchAff_ do
|
||||
-- y :: Effect String
|
||||
y = effectful (variadic blue) "hello"
|
||||
|
||||
liftEffect $ x >>= log
|
||||
liftEffect $ y >>= log
|
||||
x >>= log
|
||||
y >>= log
|
||||
-- log $ blue "blau"
|
||||
let
|
||||
x :: Effect String
|
||||
x = underline # \{ bold } -> bold # \{ green } -> effectful green "grün"
|
||||
str <- liftEffect x
|
||||
log str
|
||||
underlined :: Aff String
|
||||
underlined = underline # \{ bold } -> bold # \{ green:g } -> effectful g "grün"
|
||||
underlined >>= log
|
||||
-- let
|
||||
-- c :: Effect String
|
||||
-- c = effectfulScoped3 m rgb 123 45 67 <#> \{ underline } -> underline "Underlined reddish color"
|
||||
log $ scoped m rgb 123 45 67 # \{ underline } -> underline "Underlined reddish color"
|
||||
log $ scoped m rgb 123 45 67 # \{ underline: u } -> u "Underlined reddish color"
|
||||
|
||||
let
|
||||
c :: Effect String
|
||||
c = effectful (scoped m rgb) 123 45 67 <#> \{ underline } -> underline "Underlined reddish color"
|
||||
c :: Aff String
|
||||
c = effectful (scoped m rgb) 123 45 67 <#> \{ underline:u } -> u "Underlined reddish color"
|
||||
|
||||
log "Effect not run"
|
||||
liftEffect c >>= log
|
||||
c >>= log
|
||||
pure unit
|
||||
|
Loading…
Reference in New Issue
Block a user