Skip to content

Commit

Permalink
Format with psfmt
Browse files Browse the repository at this point in the history
  • Loading branch information
maxhallinan committed Oct 19, 2019
1 parent 443e39e commit b1b8089
Show file tree
Hide file tree
Showing 9 changed files with 71 additions and 67 deletions.
37 changes: 18 additions & 19 deletions src/Component/Redexer.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Component.Redexer (component) where

import Prelude

import Component.Step as Step
import Component.Util as U
import Control.Alt ((<|>))
Expand All @@ -20,23 +21,23 @@ import Parse as Parse
import Term (Term)
import Term as Term

type Input
= { defaultContent :: String
}
type Input =
{ defaultContent :: String
}

type State
= { currentTerm :: Maybe CurrentTerm
, defaultContent :: String
, steps :: Array Term
, parseErr :: Maybe Parse.ParseErr
, reductionOrder :: Array String
, reductions :: Map String String
}
type State =
{ currentTerm :: Maybe CurrentTerm
, defaultContent :: String
, steps :: Array Term
, parseErr :: Maybe Parse.ParseErr
, reductionOrder :: Array String
, reductions :: Map String String
}

type CurrentTerm
= { stepIndex :: Int
, termId :: String
}
type CurrentTerm =
{ stepIndex :: Int
, termId :: String
}

data Action
= Initialize
Expand All @@ -46,11 +47,9 @@ data Action
| EditorOpened { stepIndex :: Int }
| EditorClosed

type ChildSlots
= ( stepSlot :: Step.Slot SlotIndex )
type ChildSlots = ( stepSlot :: Step.Slot SlotIndex )

type SlotIndex
= Int
type SlotIndex = Int

_stepSlot :: SProxy "stepSlot"
_stepSlot = SProxy
Expand Down
53 changes: 27 additions & 26 deletions src/Component/Step.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module Component.Step
) where

import Prelude

import Component.Util as Util
import Data.Array as Array
import Data.Either (Either(..))
Expand All @@ -36,25 +37,25 @@ import Web.DOM.Node as Node
import Web.Event.Event (Event, EventType(..), stopPropagation)
import Web.Event.Event as Event
import Web.HTML.HTMLElement as HTMLElement
import Web.UIEvent.MouseEvent (MouseEvent, toEvent)
import Web.UIEvent.KeyboardEvent as KeyboardEvent
import Web.UIEvent.MouseEvent (MouseEvent, toEvent)

type Input
= { focus :: Maybe Focus
, reducedTermId :: Maybe String
, stepIndex :: Int
, stepPos :: StepPos
, term :: Term
}
type Input =
{ focus :: Maybe Focus
, reducedTermId :: Maybe String
, stepIndex :: Int
, stepPos :: StepPos
, term :: Term
}

type State
= { focus :: Maybe Focus
, interaction :: Interaction
, reducedTermId :: Maybe String
, stepIndex :: Int
, stepPos :: StepPos
, term :: Term
}
type State =
{ focus :: Maybe Focus
, interaction :: Interaction
, reducedTermId :: Maybe String
, stepIndex :: Int
, stepPos :: StepPos
, term :: Term
}

data Interaction
= Disabled
Expand All @@ -63,13 +64,15 @@ data Interaction

derive instance eqInteraction :: Eq Interaction

type WriteState
= { pendingContent :: String, parseErr :: Maybe Parse.ParseErr }
type WriteState =
{ pendingContent :: String
, parseErr :: Maybe Parse.ParseErr
}

type Focus
= { highlight :: Highlight
, termId :: String
}
type Focus =
{ highlight :: Highlight
, termId :: String
}

data Highlight
= Done
Expand Down Expand Up @@ -127,11 +130,9 @@ data Query a
= Disable { stepIndex :: Int } a
| Enable a

type Slot
= H.Slot Query Message
type Slot = H.Slot Query Message

type ChildSlots
= ()
type ChildSlots = ()

component :: H.Component HH.HTML Query Input Message Aff
component =
Expand Down
1 change: 1 addition & 0 deletions src/Component/Util.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Component.Util
) where

import Prelude

import Data.Array as Array
import Effect (Effect)
import Effect.Uncurried as EU
Expand Down
3 changes: 2 additions & 1 deletion src/Main.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Main where

import Prelude

import Component.Redexer as Redexer
import Data.Maybe (Maybe(..))
import Data.String.Common (trim)
Expand All @@ -12,9 +13,9 @@ import Web.DOM.Node (Node, childNodes, removeChild, textContent)
import Web.DOM.NodeList (toArray)
import Web.DOM.ParentNode (QuerySelector(..), querySelectorAll)
import Web.HTML (window)
import Web.HTML.Window (document)
import Web.HTML.HTMLDocument (HTMLDocument, toParentNode)
import Web.HTML.HTMLElement (fromNode)
import Web.HTML.Window (document)

main :: Effect Unit
main = do
Expand Down
18 changes: 8 additions & 10 deletions src/Parse.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Parse
) where

import Prelude

import Control.Alt ((<|>))
import Control.Lazy (fix)
import Control.Monad.State (State)
Expand All @@ -23,25 +24,22 @@ import Text.Parsing.Parser.Pos as Pos
import Text.Parsing.Parser.String as Str
import Text.Parsing.Parser.Token as Tok

type Parser a
= ParserT String ParseState a
type Parser a= ParserT String ParseState a

type ParseState
= State Context
type ParseState = State Context

type Context
= { bound :: Array String
, free :: Array String
}
type Context =
{ bound :: Array String
, free :: Array String
}

initialContext :: Context
initialContext =
{ bound: []
, free: []
}

type ParseErr
= ParseError
type ParseErr = ParseError

parse :: String -> Either ParseErr Term
parse =
Expand Down
9 changes: 5 additions & 4 deletions src/Term.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Term
) where

import Prelude

import Control.Alt ((<|>))
import Data.Array as Array
import Data.Maybe (Maybe(..), isNothing, maybe)
Expand All @@ -30,8 +31,9 @@ data Term
instance showTerm :: Show Term where
show = showTermImpl

type Ann
= { uuid :: String }
type Ann =
{ uuid :: String
}

emptyAnn :: Ann
emptyAnn = { uuid: "" }
Expand Down Expand Up @@ -84,8 +86,7 @@ shift inc term = go 0 term
Fn { paramName, body } ann -> Fn { paramName, body: go (c + 1) body } ann
Apply l r ann -> Apply (go c l) (go c r) ann

type Context
= Array String
type Context = Array String

showTermImpl :: Term -> String
showTermImpl = go []
Expand Down
7 changes: 4 additions & 3 deletions test/Main.purs
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
module Test.Main where

import Prelude

import Effect (Effect)
import Effect.Aff (launchAff_)
import Test.Parse as Parse
import Test.Term as Term
import Test.Spec.Reporter.Console (consoleReporter)
import Test.Spec.Runner (runSpec)
import Effect (Effect)
import Effect.Aff (launchAff_)
import Test.Term as Term

main :: Effect Unit
main =
Expand Down
9 changes: 5 additions & 4 deletions test/Parse.purs
Original file line number Diff line number Diff line change
@@ -1,18 +1,19 @@
module Test.Parse (spec) where

import Prelude

import Data.Array ((:))
import Data.Char.Gen (genAlpha, genDigitChar)
import Data.Either (either, isRight)
import Data.Foldable (intercalate)
import Data.NonEmpty ((:|))
import Data.Char.Gen (genAlpha, genDigitChar)
import Data.String.CodeUnits (fromCharArray, toCharArray)
import Parse (parse)
import Term (Term(..))
import Test.Spec (Spec, describe, it)
import Test.Spec.QuickCheck (quickCheck)
import Test.QuickCheck.Arbitrary (class Arbitrary)
import Test.QuickCheck.Gen (Gen, arrayOf, listOf, elements, oneOf, resize, sized)
import Test.Spec (Spec, describe, it)
import Test.Spec.QuickCheck (quickCheck)

spec :: Spec Unit
spec = do
Expand Down Expand Up @@ -153,4 +154,4 @@ genWhiteSpace :: Gen String
genWhiteSpace = fromCharArray <$> resize 3 (arrayOf genWhitespaceChar)

genWhitespaceChar :: Gen Char
genWhitespaceChar = elements $ ' ' :| toCharArray "\t\n\r"
genWhitespaceChar = elements $ ' ' :| toCharArray "\ \\n\\r"
1 change: 1 addition & 0 deletions test/Term.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Test.Term (spec) where

import Prelude

import Data.Either (Either(..))
import Effect.Aff (Aff)
import Parse (parse)
Expand Down

0 comments on commit b1b8089

Please sign in to comment.