Skip to content

Commit

Permalink
CSV reading on startup
Browse files Browse the repository at this point in the history
  • Loading branch information
Panciera committed May 2, 2016
1 parent 723bfe1 commit 3fbdee0
Show file tree
Hide file tree
Showing 6 changed files with 38 additions and 9 deletions.
2 changes: 1 addition & 1 deletion bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,6 @@
"purescript-generics" : "^0.7.2",
"purescript-globals" : "^0.2.2",
"purescript-random" : "^0.2.3",
"purescript-sets" : "^0.5.6",
"purescript-sets" : "^0.5.6"
}
}
4 changes: 4 additions & 0 deletions foo.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
genotype,segment,name,acc,year,month,day,country,host,serotype,sequence
,,11/1666,KR922405,2011,,,Thailand,Human,DENV4,ATGAACCAACGAAAGAAGGTGG
,,Br246RR/10,JN983813,2010,9,8,Brazil,Human,DENV4,ATGAACCAACGAAAAAAGGT
,,D4/Pakistan/150/2009,KF041260,2009,,,Pakistan,Human,DENV4,ATGAACCAAC
3 changes: 2 additions & 1 deletion src/Form.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module App.Form where
import Control.Monad.Eff (Eff())
import DOM (DOM)
import FileReader (FS)
import Control.Monad.Eff.Exception (EXCEPTION)
import Global (encodeURIComponent) --, readInt)
import Data.Int as Int
Expand Down Expand Up @@ -95,7 +96,7 @@ init = { name: Nothing, country: Nothing
-- In order to give Seq.State an Eq instance, it must be wrapped in NewType


type AppEffects = (random :: Rand.RANDOM, dom :: DOM )
type AppEffects = (fs :: FS, random :: Rand.RANDOM, dom :: DOM )

strToMaybe xs = if (S.null $ S.trim xs) then Nothing else Just xs

Expand Down
12 changes: 11 additions & 1 deletion src/Layout.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,16 @@ import Pux (EffModel, noEffects, mapEffects, mapState)
import Unsafe.Coerce
import Data.Either
import Data.Maybe
import FileReader (readFileBlocking)
import App.Seq as Seq
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Aff.Class (liftAff)


data Action
= Child (Form.Action)
| PageView Route
| LoadFile (Either String (Array Seq.State))
| DoChildAction Form.Action

type State =
Expand All @@ -28,7 +33,12 @@ init =


update :: forall e. Action -> State -> EffModel State Action (Form.AppEffects )
update (PageView route) state = noEffects $ state { route = route }
--update (PageView route) state = noEffects $ state { route = route }
update (PageView route) state = { state : state
, effects : [do
s <- liftEff $ readFileBlocking "foo.csv"
return $ LoadFile $ Seq.readCSV "," s]}
update (LoadFile (Right recs)) state = noEffects $ state { form = state.form { db = recs }}
update (DoChildAction (Form.RandomState state')) state = noEffects state { form = state' }
-- simply pass along the child From's actions
update (Child action) state = mapEffects DoChildAction
Expand Down
21 changes: 17 additions & 4 deletions src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,14 @@ import App.Routes (match)
import App.Layout (Action(PageView), State, view, update)
import Control.Bind ((=<<))
import Control.Monad.Eff (Eff)
import Prelude (bind, return, ($))
import Prelude (bind, return, ($), (>>=))
import Data.Maybe
import Pux (App, Config, CoreEffects, fromSimple, renderToDOM)
import Pux.Router (sampleUrl)
import Signal ((~>))
import App.Form (AppEffects)
import App.Form as Form
import Control.Monad.Eff.Class (liftEff)
-- AppEffects must be defined as a closed record with DOM and RANDOM

-- | Entry point for the browser.--
Expand All @@ -19,8 +20,9 @@ main state = do
app <- Pux.start =<< config state
renderToDOM "#app" app.html
-- | Used by hot-reloading code in support/index.js
return app
config :: State ->
return app

config :: forall e. State ->
Eff (CoreEffects (AppEffects ))
(Config State Action AppEffects)
config state = do
Expand All @@ -29,10 +31,21 @@ config state = do

-- | Map a signal of URL changes to PageView actions.
let routeSignal = urlSignal ~> \r -> PageView (match r)
return { initialState : state { form = Form.init { name = Just "foo"} }
return { initialState : state { form = Form.init { name = Just "foo" , db = [] } }
, update : update
, view : view
, inputs : [routeSignal]}

--recs <- readFileBlocking "foo.csv"
--(readFileBlocking "foo.csv") >>= \recs ->
-- return { initialState : state
-- { form = Form.init
-- { name = Just "foo"
-- , db = [] } }
-- , update : update
-- , view : view
-- , inputs : [routeSignal]}


-- | Entry point for the browser with pux-devtool injected.
debug :: State -> Eff (CoreEffects AppEffects) (App State (Pux.Devtool.Action Action))
Expand Down
5 changes: 3 additions & 2 deletions src/Seq.purs
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,7 @@ import Data.String as S
import Data.Maybe
import Data.Int as Int
--import Data.Eulalie.Parser as P
--import Data.Eulalie.String as S

--import Data.Eulalie.String as S

data Format = Fasta | CSV
readFormat = makeRead [Fasta, CSV]
Expand All @@ -44,6 +43,8 @@ instance eqFormat :: Eq Format where
readHost :: String -> Maybe Host
readHost = makeRead [Human, Mosquito]



data Host = Human | Mosquito
derive instance genericHost :: Generic Host
instance showHost :: Show Host where
Expand Down

0 comments on commit 3fbdee0

Please sign in to comment.