Movatterモバイル変換


[0]ホーム

URL:


Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

PureScript crash course targeted at Elm developers

License

NotificationsYou must be signed in to change notification settings

laurentpayot/purescript-for-elm-developers

Repository files navigation

This README file is a crash course onPureScript targeted atElm developers. It isbased on information picked from:

Sometimes I did a shameless copy-paste instead of writing a bad paraphrase. I think it is fair use but please let me know if I am infringing any copyright. Feel free to open an issue if you find a mistake.

Happy monad lifting! 🏋

Laurent


Developer Experience

VS Code Plugins

  • PureScript Language Support: Syntax highlighting for the PureScript programming language
  • PureScript IDE: PureScript IntelliSense, tooltip, errors, code actions with language-server-purescript/purs IDE server
  • Purty: PureScript formatter

Bundling

Spago is the PureScript package manager and build tool.

The PureScript compiler (transpiler) is quite fast. The compiler messages are not as friendly as with Elm, unfortunately.

Common packages

Pursuit is the home of PureScript packages documentation. It lets you search by package, module, and function names, as well as approximate type signatures.

ElmPurescriptNotes
StringData.String
MaybeData.Maybe
ResultData.EitherErr isLeft andOk isRight
ArrayData.Array[] is the empty array
ListData.ListNil is the empty list
TupleData.Tuple
DictData.Map
SetData.Set
()Data.Unit() is the emptyRow type in PureScript
NeverData.Void
DebugDebug.TraceDebug.spy is the closest thing toDebug.log

Common Functions

ElmPurescriptNotes
()unit
identityidentity
alwaysconst
neverabsurd
toStringshow
>>>>>
<<<<<
|>#
<|$
++<>Semigroup concatenation (String,Array,List,Tuple…)

Type signatures

Type signatures are separated with double colons.

sum::Int->Int->Int

Polymorphic functions in PureScript require an explicitforall to declare type variables before using them.

map::forallab. (a->b)->Maybea->Maybeb

Type holes

runApp::Foo->BarBazStringIntUnit-> ?x

If you’re not sure of a type in a type signature, you can write a type "hole" consisting of a question mark followed by a lowercase name. The compiler will generate an error and tell you what type it inferred. Note that to use type holes there must be no other compiler errors.

You can use type holes everywhere:

foo::Intfoo =1 +?what_could_this_be

Arrays

In PureScript, arrays are the most common data structure for sequences of items. They are constructed with square brackets.

importData.Array ()myArray = [2,4,3]-- Cons (prepend)myNewArray =1 : [2,4,3]-- [1,2,4,3]head [1,2,3,4]-- (Just 1)tail [1,2,3,4]-- (Just [2,3,4])init [1,2,3,4]-- (Just [1,2,3])last [1,2,3,4]-- (Just 4)-- Array access by index starting at 0[3,4,5,6,7] !!2-- (Just 5)-- Range1..5-- [1,2,3,4,5]length [2,2,2]-- 3drop3 [1,2,3,4,5]-- [4,5]take3 [1,2,3,4,5]-- [1,2,3]append [1,2,3] [4,5,6]-- [1,2,3,4,5,6]

Destructuring

You can use pattern matching for arrays of afixed length:

isEmpty::foralla.Arraya->BooleanisEmpty[] =trueisEmpty _ =falsetakeFive::ArrayInt->InttakeFive [0,1, a, b,_] = a * btakeFive _ =0

For performance reasons, PureScript doesnot provide a direct way of destructuring arrays of anunspecified length. If you need a data structure which supports this sort of matching, the recommended approach is to use lists.

Another way is to useuncons orunsnoc to break an array into its first or last element and remaining elements:

importData.Array (uncons,unsnoc)uncons [1,2,3]-- Just {head: 1, tail: [2, 3]}uncons[]-- Nothingunsnoc [1,2,3]-- Just {init: [1, 2], last: 3}unsnoc[]-- Nothingcase uncons myArrayofJust { head: x, tail: xs }-> somethingWithXandXsNothing-> somethingElse

Bewareunsnoc is O(n) where n is the length of the array.

Lists

Be careful! The literal[1,2,3] has a type ofList Int in Elm butArray Int in Purescript.

PureScript lists arelinked lists. You can create them using theCons infix alias: andNil when there is no link to the next element (end of the list).

myList =1 :2 :3 :NilmyNewList =1 : myList

Another way to create a list is from a Foldable structure (an Array in this case):

myList =List.fromFoldable [2,4,3]

Destructuring

case xsofNil-> ...-- empty list  x : rest-> ...-- head and tail

Foldables

Data.Foldable contains common functions (sum,product,minimum,maximum etc.) for data structures which can be folded, such asArray andList.

Non empty arrays/lists

There is aData.NotEmpty module that defines a genericNonEmpty data structure.:| is the infix alias for its constructor.

This quite useful to flatten cases as described in the famous"Parse, don’t validate" blog post:

importData.NonEmpty (NonEmpty, (:|))-- no Maybe when getting the headarrayHead::NonEmptyArraya->aarrayHead (x :| _) = x

Instead the genericData.NonEmpty module, use specific modules when possible:

For convenience,Data.Array.NonEmpty.Internal provides the internal constructorNonEmptyArray. Beware you can create aNonEmptyArray that is actually empty with it so use this at your own risk when you know what you are doing.

Tuples

Tuples are just a data type in Purescript. Use records when possible.

importData.Tuple (Tuple(..),fst,snd)coords2D::TupleIntIntcoords2D =Tuple1020getX::TupleIntInt->IntgetX coords = fst coordsgetY::TupleIntInt->IntgetY coords = snd coords

Nested tuples

You can use tuples that are not restricted to two elements withData.Tuple.Nested. All nested tuple functions are numbered from 1 to 10:

importData.Tuple.Nested (Tuple3,tuple3,get2)coords3D::Tuple3IntIntIntcoords3D = tuple3102030getY::Tuple3IntIntInt->IntgetY coords = get2 coords

/\ is the infix alias forTuple that allows nested tuples of arbitrary length (depth). The same alias exists for types. The previous example could be rewritten as:

importData.Tuple.Nested (type (/\), (/\),get2)coords3D::Int /\Int /\Intcoords3D =10 /\20 /\30getY::Int /\Int /\Int->IntgetY coords = get2 coords

Destructuring

distance2D::TupleIntInt->Intdistance2D (Tuple x y) =  x * x + y * ydistance3D::Int /\Int /\Int->Intdistance3D (x /\ y /\ z) =  x * x + y * y + z * z

Records

typePerson={name::String  ,age::Int}myPerson::PersonmyPerson = { name:"Bob", age:30 }edited::Personedited = myPerson { age =31 }toPerson::String->Int->PersontoPerson name age =  { name: name, age: age }toPerson2::String->Int->PersontoPerson2 name age =  { name, age }toPerson3::String->Int->PersontoPerson3 =  { name: _, age: _ }-- equivalent to `\name age -> { name, age }` (types inferred by the signature)

Property accessors

In PureScript(_ + 5) is the same as(\n -> n + 5), so(_.prop) is the same as(\r -> r.prop).

_.age myPerson-- 30_.address.street myPerson-- "Main Street"

Destructuring

personName::Person->StringpersonName { name } = namebumpAge::Person->PersonbumpAge p@{ age } =p { age = age +1 }

Pattern matching

ecoTitle {author:"Umberto Eco", title: t} =Just tecoTitle _ =NothingecoTitle {title:"Foucault's pendulum", author:"Umberto Eco"}-- (Just "Foucault's pendulum")ecoTitle {title:"The Quantum Thief", author:"Hannu Rajaniemi"}-- Nothing-- ecoTitle requires both field to type checkecoTitle {title:"The Quantum Thief"}-- Object lacks required property "author"

Row Polymorphism

Row Polymorphism is the equivalent of the extensible records concept in Elm.

-- ElmgetAge: {a |age :Int }->IntgetAge{ age}= age
-- PureScriptgetAge::forallr.{age::Int |r}->IntgetAge { age } = age

In the above example, the type variabler has kindRow Type (an unordered collection of named types, with duplicates).

where clause

Thewhere clause is "syntactic sugar" for let bindings. Functions defined below thewhere keyword can be used in the function scope and in thewhere scope.

foo::String->String->Stringfoo arg1 arg2 =  bar arg1 arg2"Welcome to PureScript!"  wherebar::String->String->String->String    bar s1 s2 s3 =      (baz s1) <> (baz s2) <> s3baz::String->String    baz s ="Hi" <> s <>"!"

Guards

Guards consist of lines starting with| followed by a predicate. They can be used to make function definitions more readable:

greater x y  | x > y =true  | otherwise =false

Exhaustibility of patterns is checked by the compiler. To be considered exhaustive, guards must clearly include a case that is always true.otherwise is a synonym fortrue and is commonly used in guards.

Guards may also be used within case expressions, which allow for inline expressions. For example, these are equivalent:

fb::Int->EffectUnitfb = log <<<case _of  n    |0 == mod n15->"FizzBuzz"    |0 == mod n3->"Fizz"    |0 == mod n5->"Buzz"    | otherwise-> show n
fb::Int->EffectUnitfb n = log x  where  x    |0 == mod n15 ="FizzBuzz"    |0 == mod n3 ="Fizz"    |0 == mod n5 ="Buzz"    | otherwise = show n

Data types

Instead of Elm’stype, PureScript usesdata.Instead of Elm’stype alias, PureScript usestype.

-- ElmtypeDirection=Up|Downtype aliasTime=Int
-- PureScriptdataDirection  =Up|DowntypeTime=Int

Newtypes

Instead of

fullName::String->String->StringfullName firstName lastName =  firstName <>"" <> lastNamefullName"Phillip""Freeman"-- "Phillip Freeman"fullName"Freeman""Phillip"-- "Freeman Phillip" wrong order!

we could write more explicit types but that would not prevent arguments ordering errors:

typeFirstName=StringtypeLastName=StringtypeFullName=StringfullName::FirstName->LastName->FullNamefullName firstName lastName =  firstName <>"" <> lastNamefullName"Phillip""Freeman"-- "Phillip Freeman"fullName"Freeman""Phillip"-- "Freeman Phillip" still wrong order!

Instead can use single constructor data types and destructure them to ensure the right arguments are provided:

dataFirstName =FirstNameStringdataLastName =LastNameStringdataFullName =FullNameStringfullName::FirstName->LastName->FullNamefullName (FirstName firstName) (LastName lastName) =  firstName <>"" <> lastNamefullName (FirstName"Phillip") (LastName"Freeman")-- "Phillip Freeman"fullName (LastName"Freeman") (FirstName"Phillip")-- compiler error!

For the compiler to optimize the output for this common pattern, it is even better to use thenewtype keyword which is especially restricted to a single constructor which contains a single argument.

newtypeFirstName =FirstNameStringnewtypeLastName =LastNameStringnewtypeFullName =FullNameString

Newtypes are especially useful when dealing with raw data as you can write a "validation" function without exposing the type constructor itself in exports. This is known as thesmart constructor pattern:

modulePassword  (Password-- not Password(..) to prevent exposing the Password constructor  ,toPassword  )wherenewtypePassword =PasswordStringtoPassword::String->EitherStringPasswordtoPassword str =if length str >=6thenRight (Password str)elseLeft"Size should be at least 6"myPassword = toPassword"123456"

Modules

Here is a full example shamelessly ripped off from the unmissablePureScript: Jordan's Reference:

moduleSyntax.Module.FullExample-- exports go here by just writing the name  (value  ,function, (>@>>>)-- aliases must be wrapped in parenthesis-- when exporting type classes, there are two rules:-- - you must precede the type class name with the keyword 'class'-- - you must also export the type class' function (or face compilation errors)  ,classTypeClass,tcFunction-- when exporting modules, you must precede the module name with-- the keyword 'module'  ,moduleExportedModule-- The type is exported, but no one can create a value of it-- outside of this module  ,ExportDataType1_ButNotItsConstructors-- syntax sugar for 'all constructors'-- Either all or none of a type's constructors must be exported  ,ExportDataType2_AndAllOfItsConstructors(..)-- Type aliases can also be exported  ,ExportedTypeAlias-- When type aliases are aliased using infix notation, one must export-- both the type alias, and the infix notation where 'type' must precede-- the infix notation  ,ExportedTypeAlias_InfixNotation,type (<|<>|>)-- Data constructor alias; exporting the alias requires you-- to also export the constructor it aliases  ,ExportedDataType3_InfixNotation(Infix_Constructor), (<||||>)  ,ExportedKind  ,ExportedKindValue  )where-- imports go here-- imports just the moduleimportModule-- import a submoduleimportModule.SubModule.SubSubModule-- import values from a moduleimportModuleValues (value1,value2)-- imports functions from a moduleimportModuleFunctions (function1,function2)-- imports function alias from a moduleimportModuleFunctionAliases ((/=), (===), (>>**>>))-- imports type class from the moduleimportModuleTypeClass (classTypeClass)-- import a type but none of its constructorsimportModuleDataType (DataType)-- import a type and one of its constructorsimportModuleDataType (DataType(Constructor1))-- import a type and some of its constructorsimportModuleDataType (DataType(Constructor1, Constructor2))-- import a type and all of its constructorsimportModuleDataType (DataType(..))-- resolve name conflicts using "hiding" keywordimportModuleNameClash1 (sameFunctionName1)importModuleNameClash2hiding (sameFunctionName1)-- resolve name conflicts using module aliasesimportModuleNameClash1asM1importModuleNameClash2asM2-- Re-export modulesimportModule1 (anInt1)asExportsimportModule2 (anInt2)asExportsimportModule3 (anInt3)asExportsimportModule4.SubModule1 (someFunction)asExportsimportModuleKind (ImportedKind,ImportedKindValue)asExportsimportPreludeimportExportedModule-- To prevent warnings from being emitted during compilation-- the above imports have to either be used here or-- re-exported (explained later in this folder).value::Intvalue =3function::String->Stringfunction x = xinfix 4functionas >@>>>classTypeClassawheretcFunction::a->a->a-- now 'sameFunctionName1' refers to ModuleF1's function, not ModuleF2's functionmyFunction1::Int->IntmyFunction1 a = sameFunctionName1 amyFunction2::Int->IntmyFunction2 a =M1.sameFunctionName1 (M2.sameFunctionName1 a)dataDifferences::M1.SameDataName->M2.SameDataName->StringdataDifferencesM1.ConstructorM2.Constructor ="code works despite name clash"dataExportDataType1_ButNotItsConstructors =Constructor1AdataExportDataType2_AndAllOfItsConstructors  =Constructor2A|Constructor2B|Constructor2CtypeExportedTypeAlias=IntdataExportedDataType3_InfixNotation =Infix_ConstructorIntIntinfixr 4Infix_Constructoras <||||>typeExportedTypeAlias_InfixNotation=Stringinfixr 4typeExportedTypeAlias_InfixNotationas <|<>|>dataExportedKindforeignimportdataExportedKindValue ::ExportedKind

Type classes

Theshow function takes a value and displays it as a string.show is defined by a type class in the Prelude module called Show, which is defined as follows:

classShowawhereshow::a->String

This code declares a new type class calledShow, which is parameterized by the type variablea.

A type class instance contains implementations of the functions defined in a type class, specialized to a particular type.You can add any type to a class, as long as you define the required functions.

For example, here is the definition of theShow type class instance forBoolean values, taken from the Prelude. We say that theBoolean typebelongs to theShowtype class.

instanceShowBooleanwhere  showtrue ="true"  showfalse ="false"

Instead of defining a differentmap for each type (Maybe, Result etc.) like in Elm, PureScript uses type classes.

For instance,map is defined once for all with theFunctor type class. AFunctor is a type constructor which supports a mapping operationmap.

classFunctorfwheremap::forallab. (a->b)->fa->fb

Type class deriving

The compiler can derive type class instances to spare you the tedium of writing boilerplate. There are a few ways to do this depending on the specific type and class being derived.

Since PureScript version 0.15.0, giving class instances a name (for generated code readability) is optional. It it generated by the compiler if missing.

Classes with built-in compiler support

Some classes have special built-in support (such asEq), and their instances can be derived from all types.

For example, if you you'd like to be able to remove duplicates from an array of an ADT usingnub, you need anEq andOrd instance. Rather than writing these manually, let the compiler do the work.

importData.Array (nub)dataMyADT  =Some|ArbitraryInt|ContentsNumberStringderive instanceEqMyADTderive instanceOrdMyADTnub [Some,Arbitrary1,Some,Some] == [Some,Arbitrary1]

Currently (in PureScript version 0.15.12), instances for the following classes can be derived by the compiler:

Derive fromnewtype

If you would like your newtype to defer to the instance that the underlying type uses for a given class, then you can use newtype deriving via thederive newtype keywords.

For example, let's say you want to add twoScore values using theSemiring instance of the wrappedInt.

newtypeScore =ScoreIntderive newtype instanceSemiringScoretenPoints::ScoretenPoints = (Score4) + (Score6)

Thatderive line replaced all this code:

-- No need to write thisinstanceSemiringScorewhere  zero =Score0  add (Score a) (Score b) =Score (a + b)  mul (Score a) (Score b) =Score (a * b)  one =Score1

Data.Newtype provides useful functions via deriving newtypes instances:

importData.Newtype (Newtype,un)newtypeAddress =AddressStringderive instanceNewtypeAddress_printAddress::Address->Eff_UnitprintAddress address =Console.log (unAddress address)

Deriving fromGeneric

For type classes without build-in support for deriving (such asShow) and for types other than newtypes where newtype deriving cannot be used, you can derive fromGeneric if the author of the type class library has implemented a generic version.

importData.Generic.Rep (classGeneric)importData.Show.Generic (genericShow)importEffect.Console (logShow)derive instanceGenericMyADT_instanceShowMyADTwhere  show = genericShow-- logs `[Some,(Arbitrary 1),(Contents 2.0 "Three")]`main = logShow [Some,Arbitrary1,Contents2.0"Three"]

Type class constraints

Here is a type class constraintEq a, separated from the rest of the type by a double arrow=>:

threeAreEqual::foralla.Eqa=>a->a->a->BooleanthreeAreEqual a1 a2 a3 = a1 == a2 && a2 == a3

This type says that we can callthreeAreEqual with any choice of typea, as long as there is anEq instance available fora.

Multiple constraints can be specified by using the=> symbol multiple times:

showCompare::foralla.Orda=>Showa=>a->a->StringshowCompare a1 a2  | a1 < a2 = show a1 <>" is less than" <> show a2  | a1 > a2 = show a1 <>" is greater than" <> show a2  | otherwise = show a1 <>" is equal to" <> show a2

The implementation of type class instances can depend on other type class instances. Those instances should be grouped in parentheses and separated by commas on the left-hand side of the=> symbol:

instance (Showa,Showb)=>Show (Eitherab)where  ...

The Warn type class

There is a type class inPrim calledWarn. When the compiler solves aWarn constraint it will trivially solve the instance and print out the message as a user defined warning.

meaningOfLife::Warn (Text"`meaningOfLife` result is hardcoded, for now.) => IntmeaningOfLife = 42

Functors

<$> is the infix alias of themap operator defined in theFunctor type class.

classFunctorfwheremap::forallab. (a->b)->fa->fb

The two following lines are equivalent:

map (\n-> n +1) (Just5)(\n-> n +1) <$> (Just5)

Applicatives

Tolift a function means to turn it into a function that works with functor-wrapped arguments. Applicative functors are functors that allow lifting of functions.

<*> is the infix alias of theapply operator defined in theApply type class (that extendsFunctor).<*> is equivalent to|> andMap in Elm (withandMap = Maybe.map2 (|>)).

TheApplicative type class extends theApply type class with apure function that takes a value and returns that value lifted into the applicative functor. WithMaybe,pure is the same asJust, and withEither,pure is the same asRight, but it is recommended to usepure in case of an eventual applicative functor change.

classApplicativefwherepure::a->faapply::f (a->b)->fa->fb-- "inherited" from the `Apply` type class

Applicative lets us perform N operations independently, then it aggregates the results for us.You are in an applicative context when usingDecoder in Elm.

Applicative validation

Let’s lift the functionfullName over aMaybe:

importPreludeimportData.MaybefullName::String->String->String->StringfullName first middle last = last <>"," <> first <>"" <> middlefullName"Phillip""A""Freeman"-- "Freeman, Phillip A"fullName <$>Just"Phillip" <*>Just"A" <*>Just"Freeman"-- Just ("Freeman, Phillip A")fullName <$>Just"Phillip" <*>Nothing <*>Just"Freeman"-- Nothing

Just like withMaybe, if we liftfullName overEither String String, we get a unique error even if multiple errors occur:

importTest.Assert (assert)importData.Either (Either(..))typeContact={firstName::String  ,lastName::String  ,address::Address}typeAddress={street::String  ,city::String  ,country::String}goodContact::ContactgoodContact =  { firstName:"John"  , lastName:"Doe"  , address:      { street:"123 Main St."      , city:"Springfield"      , country:"USA"      }  }badContact::ContactbadContact = goodContact { firstName ="", lastName ="" }nonEmptyEither::String->String->EitherStringStringnonEmptyEither fieldName value  | value =="" =Left $"Field '" <> fieldName <>"' cannot be empty"  | otherwise =Right valuevalidateContactEither::Contact->EitherStringContactvalidateContactEither c = { firstName: _, lastName: _, address: _ }  <$> nonEmptyEither"First Name" c.firstName  <*> nonEmptyEither"Last Name" c.lastName-- lifting the `c.address` value into `Either` (we could also have used `Right c.address`)  <*> pure c.addressassert $ validateContactEither goodContact ==Right goodContactassert $ validateContactEither badContact ==Left"Field 'First Name' cannot be empty"

To get an array of all the errors we can use theV functor ofData.Validation.Semigroup that it allows us to collect multiple errors using an arbitrary semigroup (such asArray String in the example below).

importData.Validation.Semigroup (V,invalid,isValid)typeErrorMessages=ArrayStringnonEmptyV::String->String->VErrorMessagesStringnonEmptyV fieldName value  | value =="" = invalid ["Field '" <> fieldName <>"' cannot be empty" ]  | otherwise = pure valuevalidateContactV::Contact->VErrorMessagesContactvalidateContactV c = { firstName: _, lastName: _, address: _ }  <$> nonEmptyV"First Name" c.firstName  <*> nonEmptyV"Last Name" c.lastName  <*> pure c.addressassert $ isValid $ validateContactV goodContactassert $ not isValid $ validateContactV badContactassert $ validateContactV badContact ==  invalid    ["Field 'First Name' cannot be empty"    ,"Field 'Last Name' cannot be empty"    ]

Applicative do notation

With theado keyword:

validateContactVAdo::Contact->VErrorMessagesContactvalidateContactVAdo c =ado  fistName<- nonEmptyV"First Name" c.firstName  lastName<- nonEmptyV"Last Name" c.lastName  address<- pure c.addressin { firstName, lastName, address }

Monads

>>= is the infix alias of thebind operator defined in theBind type class (that extendsApply).>>= is equivalent to|> andThen in Elm.

TheMonad type class combines the operations of theBind and Applicative type classes. Therefore,Monad instances represent type constructors which support both sequential composition and function lifting.

classMonadmwherebind::ma-> (a->mb)->mb

So, to define a monad we need to define themap,apply,pure andbind operations:

dataBoxa =BoxainstanceFunctorBoxwheremap::forallab. (a->b)->Boxa->Boxb  map f (Box a) =Box (f a)instanceApplyBoxwhereapply::forallab.Box (a->b)->Boxa->Boxb  apply (Box f) (Box a) =Box (f a)instanceApplicativeBoxwherepure::foralla.a->Boxa  pure a =Box ainstanceBindBoxwherebind::forallab.Boxa-> (a->Boxb)->Boxb  bind (Box a) f = f ainstanceMonadBox

Monadic operations operate sequentially not concurrently. That’s great when we have a dependency between the operations e.g. lookup user_id based on email then fetch the inbox based on the user_id. But for independent operations monadic calls are very inefficient as they are inherently sequential. Monads fail fast which makes them poor for form validation and similar use cases. Once something "fails" the operation aborts.You are in a monadic context when usingTask in Elm.

Monad do-notation

Thedo keyword is "syntactic sugar" for chained>>=. It removes the need for indentations.

foo::BoxUnitfoo =-- only call `(\x -> ...)` if `getMyInt` actually produces something  getMyInt >>= (\x->let y = x +4in toString y >>= (\z->        print z      )    )

is the same as

foo::BoxUnitfoo =do  x<- getMyIntlet y = x +4-- `in` keyword not needed  z<- toString y  print z-- not `value <- computation` but just `computation`

Effects

Themain function of PureScript programs uses theEffect monad for side effects:

importEffect.Random (random)-- random :: Effect Numbermain::EffectUnitmain =  (log"Below is a random number between 0.0 and 1.0:") >>= (\_->    random >>= (\n->      log $ show n    )  )

and is more readable using the do-notation:

main::EffectUnitmain =do  log"Below is a random number between 0.0 and 1.0:"  n<- random  log $ show n

The above example works because the last line has alog that returnsEffect Unit.We can use thevoid function to ignore the type wrapped by a Functor and replace it withUnit:

void::forallfa.Functorf=>fa->fUnit

That is useful when using the do-notation:

main::EffectUnitmain =do  log"Generating random number..."  void random

Asynchronous Effects (Aff)

Using asynchronous effects in PureScript is like using promises in JavaScript.

PureScript applications use themain function in the context of theEffect monad. To start theApp monad context from theEffect context, we use thelaunchAff function (orlaunchAff_ which isvoid $ launchAff).

When we have an Effect-based computation that we want to run in some other monadic context, we can useliftEffect fromEffect.Class if the target monad has an instance forMonadEffect:

class (Monadm)MonadEffectmwhere-- same as liftEffect :: forall a. Effect a -> m aliftEffect::Effect ~>m

Aff has an instance forMonadEffect, so we can liftEffect-based computations (such aslog) into anAff monadic context:

importPreludeimportEffect (Effect)importEffect.Aff (Milliseconds(..),delay,launchAff_)importEffect.Class (liftEffect)importEffect.Console (log)importEffect.Timer (setTimeout,clearTimeout)main::EffectUnitmain = launchAff_do  timeoutID<- liftEffect $ setTimeout1000 (log"This will run after 1 second")  delay (Milliseconds1300.0)  liftEffectdo    log"Now cancelling timeout"    clearTimeout timeoutID

We can run multiple computations concurrently withforkAff. Then, we'll usejoinFiber to ensure all computations are finished before we do another computation.

importEffect (Effect)importEffect.Aff (Milliseconds(..),delay,forkAff,joinFiber,launchAff_)main::EffectUnitmain = launchAff_do  fiber1<- forkAffdo    liftEffect $ log"Fiber 1: Waiting for 1 second until completion."    delay $Milliseconds1000.0    liftEffect $ log"Fiber 1: Finished computation."  fiber2<- forkAffdo    liftEffect $ log"Fiber 2: Computation 1 (takes 300 ms)."    delay $Milliseconds300.0    liftEffect $ log"Fiber 2: Computation 2 (takes 300 ms)."    delay $Milliseconds300.0    liftEffect $ log"Fiber 2: Computation 3 (takes 500 ms)."    delay $Milliseconds500.0    liftEffect $ log"Fiber 2: Finished computation."  fiber3<- forkAffdo    liftEffect $ log"Fiber 3: Nothing to do. Just return immediately."    liftEffect $ log"Fiber 3: Finished computation."  joinFiber fiber1  liftEffect $ log"Fiber 1 has finished. Now joining on fiber 2"  joinFiber fiber2  liftEffect $ log"Fiber 3 has finished. Now joining on fiber 3"  joinFiber fiber3  liftEffect $ log"Fiber 3 has finished. All fibers have finished their computation."

If instead offorkAff we usedsuspendAff, then the fibers would not be runconcurrently as soon as defined, but they would be suspended and ransequentially one by one after their respectivejoinFiber.

Foreign Function Interface (FFI)

Calling PureScript from JavaScript

-- PurescriptmoduleToolswhereimportPrelude-- find the greatest common divisorgcd::Int->Int->Intgcd n m  | n ==0 = m  | m ==0 = n  | n > m = gcd (n - m) m  | otherwise = gcd (m - n) n

PureScript functions always get turned into Javascript functions of a single argument, so we need to apply its arguments one-by-one:

// JavaScriptimport{gcd}from'Tools'gcd(15)(20)

Calling Javascript from PureScript

Foreign Modules

A foreign module is just an ES module which is associated with a PureScript module.

  • All the ES module exports must be of the formexport const name = value orexport function name() { ... }.
  • The PureScript module must have the same as the ES one but with the.purs extension. It contains the signatures of the exports.
Unary functions
// JavaScript (src/Interest.js)exportfunctioncalculateInterest(amount){returnamount*0.1}
-- PureScript (src/Interest.purs)moduleInterestwhereforeignimportcalculateInterest::Number->Number
Functions of Multiple Arguments

PureScript functions are curried by default, so Javascript functions of multiple arguments require special treatment.

// JavaScriptexportfunctioncalculateInterest(amount,months){returnamount*Math.exp(0.1,months)}
-- PureScriptmoduleInterestwhere-- available for function arities from 0 to 10importData.Function.Uncurried (Fn2)foreignimportcalculateInterest::Fn2NumberNumberNumber

We can write a curried wrapper function in PureScript which will allow partial application:

calculateInterestCurried::Number->Number->NumbercalculateInterestCurried = runFn2 calculateInterest

An alternative is to use curried functions in the native module, using multiple nested functions, each with a single argument:

// JavaScriptexportconstcalculateInterest=amount=>months=>amount*Math.exp(0.1,months)

This time, we can assign the curried function type directly:

-- PureScriptforeignimportcalculateInterest::Number->Number->Number

Promises

Promises in JavaScript translate directly to asynchronous effects in PureScript with the help ofPromise.Aff.

In JavaScript, you need to wrap asynchronous functions in a PureScript Effect with a "thunk"() => so the function is not considered pure and is run every time:

// JavaScriptexportconstcatBase64JS=text=>fontSize=>async()=>{constresponse=awaitfetch(`https://cataas.com/cat/says/${text}?fontSize=${fontSize}&fontColor=red`)constarray=awaitresponse.body.getReader().read()returnbtoa(String.fromCharCode.apply(null,array.value))}

Then in PureScript use thetoAffE function:

-- PureScriptimportPromise.Aff (Promise,toAffE)foreignimportcatBase64JS::String->Int->Effect (PromiseString)catBase64::String->Int->AffStringcatBase64 text fontSize = toAffE $ catBase64JS text fontSize

Sanitizing Foreign Data

It is important to sanitize data when working with values returned from Javascript functions using the FFI. For this we will usepurescript-foreign-generic.

importData.ForeignimportData.Foreign.GenericimportData.Foreign.JSON

purescript-foreign-generic has the following functions:

parseJSON::String->FForeigndecodeJSON::foralla.Decodea=>String->Fa

F is a type alias:

typeF=Except (NonEmptyListForeignError)

Note:The usage of theF alias is now discouraged.

Except is an monad for handling exceptions, much likeEither. We can convert a value in theF monad into a value in theEither monad by using therunExcept function.

importControl.Monad.ExceptrunExcept (decodeJSON"\"Testing\""::FString)-- Right "Testing"runExcept (decodeJSON"true"::FBoolean)-- Right truerunExcept (decodeJSON"[1, 2, 3]"::F (ArrayInt))-- Right [1, 2, 3]runExcept (decodeJSON"[1, 2, true]"::F (ArrayInt))-- Left (NonEmptyList (NonEmpty (ErrorAtIndex 2 (TypeMismatch "Int" "Boolean")) Nil))

Real-world JSON documents contain null and undefined values, so we need to be able to handle those too.

purescript-foreign-generic defines a type constructors which solves this problem:NullOrUndefined. It uses theMaybe type constructor internally to represent missing values.

The module also provides a functionunNullOrUndefined to unwrap the inner value. We can lift the appropriate function over thedecodeJSON action to parse JSON documents which permit null values:

importData.Foreign.NullOrUndefinedrunExcept (unNullOrUndefined <$> decodeJSON"42"::F (NullOrUndefinedInt))-- Right (Just 42)runExcept (unNullOrUndefined <$> decodeJSON"null"::F (NullOrUndefinedInt))-- Right Nothing

To parse arrays of integers where each element might be null, we can lift the functionmap unNullOrUndefined over thedecodeJSON action:

runExcept (map unNullOrUndefined <$> decodeJSON"[1, 2, null]"::F (Array (NullOrUndefinedInt)))-- Right [(Just 1),(Just 2),Nothing]

Front-end frameworks

InThe state of PureScript 2023 survey results, at page 24, you can see a chart of the most used front-end frameworks:

PureScript frameworks usage chart for 2023

Flame example

This repo contains a minimal Flame example with a counter increment/decrement buttons, random number generation, synchronous and asynchronous FFI calls, subscription and decoding of a JSON object.

Installation

npm i

Vite setup notes

  • When usingPureScript IDE for VS code the project is built every time you save a file. There is no need for a special Vite plugin.output/Main/index.js is simply imported in the JavasScript entry file.
  • Terser is used for better compression results.

Go further

We only covered the basics of PureScript here. If you want to learn more, check out the following resources:

License

MIT

Stargazers ❤️

Stargazers repo roster for @laurentpayot/purescript-for-elm-developers

Releases

No releases published

Packages

No packages published

[8]ページ先頭

©2009-2025 Movatter.jp